Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (eir@cis.upenn.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Singletons.Prelude.List
Contents
Description
Defines functions and datatypes relating to the singleton for '[]',
including a singletons version of a few of 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.
- data family Sing (a :: k)
- type SList = (Sing :: [a] -> Type)
- type family (a :: [a]) :++ (a :: [a]) :: [a] where ...
- (%:++) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:++$) t) t :: [a])
- type family Head (a :: [a]) :: a where ...
- sHead :: forall t. Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Last (a :: [a]) :: a where ...
- sLast :: forall t. Sing t -> Sing (Apply LastSym0 t :: a)
- type family Tail (a :: [a]) :: [a] where ...
- sTail :: forall t. Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Init (a :: [a]) :: [a] where ...
- sInit :: forall t. Sing t -> Sing (Apply InitSym0 t :: [a])
- type family Null (a :: [a]) :: Bool where ...
- sNull :: forall t. Sing t -> Sing (Apply NullSym0 t :: Bool)
- type family Length (a :: [a]) :: Nat where ...
- sLength :: forall t. Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Map (a :: TyFun a b -> Type) (a :: [a]) :: [b] where ...
- sMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: [b])
- type family Reverse (a :: [a]) :: [a] where ...
- sReverse :: forall t. Sing t -> Sing (Apply ReverseSym0 t :: [a])
- type family Intersperse (a :: a) (a :: [a]) :: [a] where ...
- sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a])
- type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ...
- sIntercalate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a])
- type family Transpose (a :: [[a]]) :: [[a]] where ...
- sTranspose :: forall t. Sing t -> Sing (Apply TransposeSym0 t :: [[a]])
- type family Subsequences (a :: [a]) :: [[a]] where ...
- sSubsequences :: forall t. Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]])
- type family Permutations (a :: [a]) :: [[a]] where ...
- sPermutations :: forall t. Sing t -> Sing (Apply PermutationsSym0 t :: [[a]])
- type family Foldl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b)
- type family Foldl' (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldl' :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b)
- type family Foldl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a)
- type family Foldl1' (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldl1' :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldl1'Sym0 t) t :: a)
- type family Foldr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: b where ...
- sFoldr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b)
- type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ...
- sFoldr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a)
- type family Concat (a :: [[a]]) :: [a] where ...
- sConcat :: forall t. Sing t -> Sing (Apply ConcatSym0 t :: [a])
- type family ConcatMap (a :: TyFun a [b] -> Type) (a :: [a]) :: [b] where ...
- sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b])
- type family And (a :: [Bool]) :: Bool where ...
- sAnd :: forall t. Sing t -> Sing (Apply AndSym0 t :: Bool)
- type family Or (a :: [Bool]) :: Bool where ...
- sOr :: forall t. Sing t -> Sing (Apply OrSym0 t :: Bool)
- type family Any_ (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- sAny_ :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Any_Sym0 t) t :: Bool)
- type family All (a :: TyFun a Bool -> Type) (a :: [a]) :: Bool where ...
- sAll :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool)
- type family Sum (a :: [a]) :: a where ...
- sSum :: forall t. SNum a => Sing t -> Sing (Apply SumSym0 t :: a)
- type family Product (a :: [a]) :: a where ...
- sProduct :: forall t. SNum a => Sing t -> Sing (Apply ProductSym0 t :: a)
- type family Maximum (a :: [a]) :: a where ...
- sMaximum :: forall t. SOrd a => Sing t -> Sing (Apply MaximumSym0 t :: a)
- type family Minimum (a :: [a]) :: a where ...
- sMinimum :: forall t. SOrd a => Sing t -> Sing (Apply MinimumSym0 t :: a)
- any_ :: forall a. (a -> Bool) -> [a] -> Bool
- type family Scanl (a :: TyFun b (TyFun a b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
- sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b])
- type family Scanl1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
- sScanl1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: [a])
- type family Scanr (a :: TyFun a (TyFun b b -> Type) -> Type) (a :: b) (a :: [a]) :: [b] where ...
- sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b])
- type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ...
- sScanr1 :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: [a])
- type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
- sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y]))
- type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ...
- sMapAccumR :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y]))
- type family Replicate (a :: Nat) (a :: a) :: [a] where ...
- sReplicate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a])
- type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ...
- sUnfoldr :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: [a])
- type family Take (a :: Nat) (a :: [a]) :: [a] where ...
- sTake :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Nat) (a :: [a]) :: [a] where ...
- sDrop :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Nat) (a :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sTakeWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sDropWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sDropWhileEnd :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a])
- type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sSpan :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sBreak :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family Group (a :: [a]) :: [[a]] where ...
- sGroup :: forall t. SEq a => Sing t -> Sing (Apply GroupSym0 t :: [[a]])
- type family Inits (a :: [a]) :: [[a]] where ...
- sInits :: forall t. Sing t -> Sing (Apply InitsSym0 t :: [[a]])
- type family Tails (a :: [a]) :: [[a]] where ...
- sTails :: forall t. Sing t -> Sing (Apply TailsSym0 t :: [[a]])
- type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsPrefixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsSuffixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool)
- type family IsInfixOf (a :: [a]) (a :: [a]) :: Bool where ...
- sIsInfixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool)
- type family Elem (a :: a) (a :: [a]) :: Bool where ...
- sElem :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool)
- type family NotElem (a :: a) (a :: [a]) :: Bool where ...
- sNotElem :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool)
- type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b)
- type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ...
- sFind :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a)
- type family Filter (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ...
- sFilter :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ...
- sPartition :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family (a :: [a]) :!! (a :: Nat) :: a where ...
- (%:!!) :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply (:!!$) t) t :: a)
- type family ElemIndex (a :: a) (a :: [a]) :: Maybe Nat where ...
- sElemIndex :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat)
- type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ...
- sElemIndices :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat])
- type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ...
- sFindIndex :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat)
- type family FindIndices (a :: TyFun a Bool -> Type) (a :: [a]) :: [Nat] where ...
- sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat])
- type family Zip (a :: [a]) (a :: [b]) :: [(a, b)] where ...
- sZip :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: [(a, b)])
- type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)])
- type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ...
- sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c])
- type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ...
- sZipWith3 :: forall t t t t. Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d])
- type family Unzip (a :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall t. Sing t -> Sing (Apply UnzipSym0 t :: ([a], [b]))
- type family Unzip3 (a :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall t. Sing t -> Sing (Apply Unzip3Sym0 t :: ([a], [b], [c]))
- type family Unzip4 (a :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall t. Sing t -> Sing (Apply Unzip4Sym0 t :: ([a], [b], [c], [d]))
- type family Unzip5 (a :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall t. Sing t -> Sing (Apply Unzip5Sym0 t :: ([a], [b], [c], [d], [e]))
- type family Unzip6 (a :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall t. Sing t -> Sing (Apply Unzip6Sym0 t :: ([a], [b], [c], [d], [e], [f]))
- type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall t. Sing t -> Sing (Apply Unzip7Sym0 t :: ([a], [b], [c], [d], [e], [f], [g]))
- type family Nub (a :: [a]) :: [a] where ...
- sNub :: forall t. SEq a => Sing t -> Sing (Apply NubSym0 t :: [a])
- type family Delete (a :: a) (a :: [a]) :: [a] where ...
- sDelete :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply DeleteSym0 t) t :: [a])
- type family (a :: [a]) :\\ (a :: [a]) :: [a] where ...
- (%:\\) :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply (:\\$) t) t :: [a])
- type family Union (a :: [a]) (a :: [a]) :: [a] where ...
- sUnion :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply UnionSym0 t) t :: [a])
- type family Intersect (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersect :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a])
- type family Insert (a :: a) (a :: [a]) :: [a] where ...
- sInsert :: forall t t. SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: [a])
- type family Sort (a :: [a]) :: [a] where ...
- sSort :: forall t. SOrd a => Sing t -> Sing (Apply SortSym0 t :: [a])
- type family NubBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [a] where ...
- sNubBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: [a])
- type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
- sDeleteBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a])
- type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a])
- type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sUnionBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a])
- type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ...
- sIntersectBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a])
- type family GroupBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) :: [[a]] where ...
- sGroupBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [[a]])
- type family SortBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: [a] where ...
- sSortBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: [a])
- type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ...
- sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a])
- type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
- sMaximumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a)
- type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ...
- sMinimumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a)
- type family GenericLength (a :: [a]) :: i where ...
- sGenericLength :: forall t. SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i)
- 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 LengthSym0 l
- type LengthSym1 t = Length 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 TransposeSym0 l
- type TransposeSym1 t = Transpose 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 SumSym0 l
- type SumSym1 t = Sum t
- data ProductSym0 l
- type ProductSym1 t = Product t
- data MaximumSym0 l
- type MaximumSym1 t = Maximum t
- data MinimumSym0 l
- type MinimumSym1 t = Minimum 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 ReplicateSym0 l
- data ReplicateSym1 l l
- type ReplicateSym2 t t = Replicate t t
- data UnfoldrSym0 l
- data UnfoldrSym1 l l
- type UnfoldrSym2 t t = Unfoldr t 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 GroupSym0 l
- type GroupSym1 t = Group 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 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 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 NubSym0 l
- type NubSym1 t = Nub 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 UnionSym0 l
- data UnionSym1 l l
- type UnionSym2 t t = Union 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 NubBySym0 l
- data NubBySym1 l l
- type NubBySym2 t t = NubBy t 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 UnionBySym0 l
- data UnionBySym1 l l
- data UnionBySym2 l l l
- type UnionBySym3 t t t = UnionBy t t t
- data IntersectBySym0 l
- data IntersectBySym1 l l
- data IntersectBySym2 l l l
- type IntersectBySym3 t t t = IntersectBy t t t
- data GroupBySym0 l
- data GroupBySym1 l l
- type GroupBySym2 t t = GroupBy t t
- 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 GenericLengthSym0 l
- type GenericLengthSym1 t = GenericLength t
The singleton for lists
The singleton kind-indexed data family.
Instances
data Sing Bool # | |
data Sing Ordering # | |
data Sing * # | |
data Sing Nat # | |
data Sing Symbol # | |
data Sing () # | |
data Sing [a0] # | |
data Sing (Maybe a0) # | |
data Sing (NonEmpty a0) # | |
data Sing (Either a0 b0) # | |
data Sing (a0, b0) # | |
data Sing ((~>) k1 k2) # | |
data Sing (a0, b0, c0) # | |
data Sing (a0, b0, c0, d0) # | |
data Sing (a0, b0, c0, d0, e0) # | |
data Sing (a0, b0, c0, d0, e0, f0) # | |
data Sing (a0, b0, c0, d0, e0, f0, g0) # | |
Though Haddock doesn't show it, the Sing
instance above declares
constructors
SNil :: Sing '[] SCons :: Sing (h :: k) -> Sing (t :: [k]) -> Sing (h ': t)
Basic functions
type family Length (a :: [a]) :: Nat where ... #
Equations
Length '[] = FromInteger 0 | |
Length ((:) _z_6989586621679998590 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply LengthSym0 xs) |
List transformations
type family Intersperse (a :: a) (a :: [a]) :: [a] where ... #
Equations
Intersperse _z_6989586621680001619 '[] = '[] | |
Intersperse sep ((:) x xs) = Apply (Apply (:$) x) (Apply (Apply PrependToAllSym0 sep) xs) |
sIntersperse :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: [a]) #
type family Intercalate (a :: [a]) (a :: [[a]]) :: [a] where ... #
Equations
Intercalate xs xss = Apply ConcatSym0 (Apply (Apply IntersperseSym0 xs) xss) |
sIntercalate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply IntercalateSym0 t) t :: [a]) #
sTranspose :: forall t. Sing t -> Sing (Apply TransposeSym0 t :: [[a]]) #
type family Subsequences (a :: [a]) :: [[a]] where ... #
Equations
Subsequences xs = Apply (Apply (:$) '[]) (Apply NonEmptySubsequencesSym0 xs) |
sSubsequences :: forall t. Sing t -> Sing (Apply SubsequencesSym0 t :: [[a]]) #
type family Permutations (a :: [a]) :: [[a]] where ... #
sPermutations :: forall t. Sing t -> Sing (Apply PermutationsSym0 t :: [[a]]) #
Reducing lists (folds)
sFoldl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) #
sFoldl' :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) #
sFoldr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) #
type family Foldr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
Foldr1 _z_6989586621680000843 '[x] = x | |
Foldr1 f ((:) x ((:) wild_6989586621679997571 wild_6989586621679997573)) = Apply (Apply f x) (Apply (Apply Foldr1Sym0 f) (Let6989586621680000851XsSym4 f x wild_6989586621679997571 wild_6989586621679997573)) | |
Foldr1 _z_6989586621680000870 '[] = Apply ErrorSym0 "Data.Singletons.List.foldr1: empty list" |
Special folds
sConcatMap :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) #
type family Sum (a :: [a]) :: a where ... #
Equations
Sum l = Apply (Apply (Let6989586621679998623Sum'Sym1 l) l) (FromInteger 0) |
type family Product (a :: [a]) :: a where ... #
Equations
Product l = Apply (Apply (Let6989586621679998599ProdSym1 l) l) (FromInteger 1) |
Building lists
Scans
sScanl :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: [b]) #
sScanr :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: [b]) #
type family Scanr1 (a :: TyFun a (TyFun a a -> Type) -> Type) (a :: [a]) :: [a] where ... #
Equations
Scanr1 _z_6989586621680000648 '[] = '[] | |
Scanr1 _z_6989586621680000651 '[x] = Apply (Apply (:$) x) '[] | |
Scanr1 f ((:) x ((:) wild_6989586621679997579 wild_6989586621679997581)) = Case_6989586621680000697 f x wild_6989586621679997579 wild_6989586621679997581 (Let6989586621680000678Scrutinee_6989586621679997577Sym4 f x wild_6989586621679997579 wild_6989586621679997581) |
Accumulating maps
type family MapAccumL (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #
sMapAccumL :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumLSym0 t) t) t :: (acc, [y])) #
type family MapAccumR (a :: TyFun acc (TyFun x (acc, y) -> Type) -> Type) (a :: acc) (a :: [x]) :: (acc, [y]) where ... #
sMapAccumR :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MapAccumRSym0 t) t) t :: (acc, [y])) #
Cyclical lists
type family Replicate (a :: Nat) (a :: a) :: [a] where ... #
Equations
Replicate n x = Case_6989586621679998583 n x (Let6989586621679998575Scrutinee_6989586621679997663Sym2 n x) |
sReplicate :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply ReplicateSym0 t) t :: [a]) #
Unfolding
type family Unfoldr (a :: TyFun b (Maybe (a, b)) -> Type) (a :: b) :: [a] where ... #
Equations
Unfoldr f b = Case_6989586621680000290 f b (Let6989586621680000282Scrutinee_6989586621679997583Sym2 f b) |
Sublists
Extracting sublists
sTakeWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) #
sDropWhile :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) #
type family DropWhileEnd (a :: TyFun a Bool -> Type) (a :: [a]) :: [a] where ... #
sDropWhileEnd :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply DropWhileEndSym0 t) t :: [a]) #
type family Span (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #
Equations
Span _z_6989586621679998917 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679998920XsSym1 _z_6989586621679998917)) (Let6989586621679998920XsSym1 _z_6989586621679998917) | |
Span p ((:) x xs') = Case_6989586621679998953 p x xs' (Let6989586621679998940Scrutinee_6989586621679997643Sym3 p x xs') |
type family Break (a :: TyFun a Bool -> Type) (a :: [a]) :: ([a], [a]) where ... #
Equations
Break _z_6989586621679998812 '[] = Apply (Apply Tuple2Sym0 (Let6989586621679998815XsSym1 _z_6989586621679998812)) (Let6989586621679998815XsSym1 _z_6989586621679998812) | |
Break p ((:) x xs') = Case_6989586621679998848 p x xs' (Let6989586621679998835Scrutinee_6989586621679997645Sym3 p x xs') |
type family Group (a :: [a]) :: [[a]] where ... #
Equations
Group xs = Apply (Apply GroupBySym0 (:==$)) xs |
Predicates
type family IsPrefixOf (a :: [a]) (a :: [a]) :: Bool where ... #
Equations
IsPrefixOf '[] '[] = TrueSym0 | |
IsPrefixOf '[] ((:) _z_6989586621680000222 _z_6989586621680000225) = TrueSym0 | |
IsPrefixOf ((:) _z_6989586621680000228 _z_6989586621680000231) '[] = FalseSym0 | |
IsPrefixOf ((:) x xs) ((:) y ys) = Apply (Apply (:&&$) (Apply (Apply (:==$) x) y)) (Apply (Apply IsPrefixOfSym0 xs) ys) |
sIsPrefixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) #
type family IsSuffixOf (a :: [a]) (a :: [a]) :: Bool where ... #
Equations
IsSuffixOf x y = Apply (Apply IsPrefixOfSym0 (Apply ReverseSym0 x)) (Apply ReverseSym0 y) |
sIsSuffixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsSuffixOfSym0 t) t :: Bool) #
sIsInfixOf :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsInfixOfSym0 t) t :: Bool) #
Searching lists
Searching by equality
type family Lookup (a :: a) (a :: [(a, b)]) :: Maybe b where ... #
Equations
Lookup _key '[] = NothingSym0 | |
Lookup key ((:) '(x, y) xys) = Case_6989586621679998727 key x y xys (Let6989586621679998708Scrutinee_6989586621679997659Sym4 key x y xys) |
sLookup :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply LookupSym0 t) t :: Maybe b) #
Searching with a predicate
type family Find (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe a where ... #
Equations
Find p a_6989586621679999203 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FilterSym0 p)) a_6989586621679999203 |
sPartition :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) #
Indexing lists
sElemIndex :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndexSym0 t) t :: Maybe Nat) #
type family ElemIndices (a :: a) (a :: [a]) :: [Nat] where ... #
Equations
ElemIndices x a_6989586621680000105 = Apply (Apply FindIndicesSym0 (Apply (:==$) x)) a_6989586621680000105 |
sElemIndices :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemIndicesSym0 t) t :: [Nat]) #
type family FindIndex (a :: TyFun a Bool -> Type) (a :: [a]) :: Maybe Nat where ... #
Equations
FindIndex p a_6989586621680000118 = Apply (Apply (Apply (:.$) ListToMaybeSym0) (Apply FindIndicesSym0 p)) a_6989586621680000118 |
sFindIndex :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndexSym0 t) t :: Maybe Nat) #
sFindIndices :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply FindIndicesSym0 t) t :: [Nat]) #
Zipping and unzipping lists
type family Zip3 (a :: [a]) (a :: [b]) (a :: [c]) :: [(a, b, c)] where ... #
Equations
Zip3 ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply Tuple3Sym0 a) b) c)) (Apply (Apply (Apply Zip3Sym0 as) bs) cs) | |
Zip3 '[] '[] '[] = '[] | |
Zip3 '[] '[] ((:) _z_6989586621679999954 _z_6989586621679999957) = '[] | |
Zip3 '[] ((:) _z_6989586621679999960 _z_6989586621679999963) '[] = '[] | |
Zip3 '[] ((:) _z_6989586621679999966 _z_6989586621679999969) ((:) _z_6989586621679999972 _z_6989586621679999975) = '[] | |
Zip3 ((:) _z_6989586621679999978 _z_6989586621679999981) '[] '[] = '[] | |
Zip3 ((:) _z_6989586621679999984 _z_6989586621679999987) '[] ((:) _z_6989586621679999990 _z_6989586621679999993) = '[] | |
Zip3 ((:) _z_6989586621679999996 _z_6989586621679999999) ((:) _z_6989586621680000002 _z_6989586621680000005) '[] = '[] |
sZip3 :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Zip3Sym0 t) t) t :: [(a, b, c)]) #
type family ZipWith (a :: TyFun a (TyFun b c -> Type) -> Type) (a :: [a]) (a :: [b]) :: [c] where ... #
Equations
ZipWith f ((:) x xs) ((:) y ys) = Apply (Apply (:$) (Apply (Apply f x) y)) (Apply (Apply (Apply ZipWithSym0 f) xs) ys) | |
ZipWith _z_6989586621679999912 '[] '[] = '[] | |
ZipWith _z_6989586621679999915 ((:) _z_6989586621679999918 _z_6989586621679999921) '[] = '[] | |
ZipWith _z_6989586621679999924 '[] ((:) _z_6989586621679999927 _z_6989586621679999930) = '[] |
sZipWith :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: [c]) #
type family ZipWith3 (a :: TyFun a (TyFun b (TyFun c d -> Type) -> Type) -> Type) (a :: [a]) (a :: [b]) (a :: [c]) :: [d] where ... #
Equations
ZipWith3 z ((:) a as) ((:) b bs) ((:) c cs) = Apply (Apply (:$) (Apply (Apply (Apply z a) b) c)) (Apply (Apply (Apply (Apply ZipWith3Sym0 z) as) bs) cs) | |
ZipWith3 _z_6989586621679999817 '[] '[] '[] = '[] | |
ZipWith3 _z_6989586621679999820 '[] '[] ((:) _z_6989586621679999823 _z_6989586621679999826) = '[] | |
ZipWith3 _z_6989586621679999829 '[] ((:) _z_6989586621679999832 _z_6989586621679999835) '[] = '[] | |
ZipWith3 _z_6989586621679999838 '[] ((:) _z_6989586621679999841 _z_6989586621679999844) ((:) _z_6989586621679999847 _z_6989586621679999850) = '[] | |
ZipWith3 _z_6989586621679999853 ((:) _z_6989586621679999856 _z_6989586621679999859) '[] '[] = '[] | |
ZipWith3 _z_6989586621679999862 ((:) _z_6989586621679999865 _z_6989586621679999868) '[] ((:) _z_6989586621679999871 _z_6989586621679999874) = '[] | |
ZipWith3 _z_6989586621679999877 ((:) _z_6989586621679999880 _z_6989586621679999883) ((:) _z_6989586621679999886 _z_6989586621679999889) '[] = '[] |
sZipWith3 :: forall t t t t. Sing t -> Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply (Apply ZipWith3Sym0 t) t) t) t :: [d]) #
type family Unzip7 (a :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... #
Special lists
"Set" operations
sIntersect :: forall t t. SEq a => Sing t -> Sing t -> Sing (Apply (Apply IntersectSym0 t) t :: [a]) #
Ordered lists
type family Insert (a :: a) (a :: [a]) :: [a] where ... #
Equations
Insert e ls = Apply (Apply (Apply InsertBySym0 CompareSym0) e) ls |
type family Sort (a :: [a]) :: [a] where ... #
Equations
Sort a_6989586621679999439 = Apply (Apply SortBySym0 CompareSym0) a_6989586621679999439 |
Generalized functions
The "By
" operations
User-supplied equality (replacing an Eq
context)
The predicate is assumed to define an equivalence.
type family DeleteBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #
sDeleteBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteBySym0 t) t) t :: [a]) #
type family DeleteFirstsBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
Equations
DeleteFirstsBy eq a_6989586621679999508 a_6989586621679999510 = Apply (Apply (Apply FoldlSym0 (Apply FlipSym0 (Apply DeleteBySym0 eq))) a_6989586621679999508) a_6989586621679999510 |
sDeleteFirstsBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply DeleteFirstsBySym0 t) t) t :: [a]) #
type family UnionBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
sUnionBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply UnionBySym0 t) t) t :: [a]) #
type family IntersectBy (a :: TyFun a (TyFun a Bool -> Type) -> Type) (a :: [a]) (a :: [a]) :: [a] where ... #
Equations
IntersectBy _z_6989586621679999222 '[] '[] = '[] | |
IntersectBy _z_6989586621679999225 '[] ((:) _z_6989586621679999228 _z_6989586621679999231) = '[] | |
IntersectBy _z_6989586621679999234 ((:) _z_6989586621679999237 _z_6989586621679999240) '[] = '[] | |
IntersectBy eq ((:) wild_6989586621679997629 wild_6989586621679997631) ((:) wild_6989586621679997633 wild_6989586621679997635) = Apply (Apply FilterSym0 (Apply (Apply (Apply (Apply (Apply Lambda_6989586621679999299Sym0 eq) wild_6989586621679997629) wild_6989586621679997631) wild_6989586621679997633) wild_6989586621679997635)) (Let6989586621679999248XsSym5 eq wild_6989586621679997629 wild_6989586621679997631 wild_6989586621679997633 wild_6989586621679997635) |
sIntersectBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply IntersectBySym0 t) t) t :: [a]) #
User-supplied comparison (replacing an Ord
context)
The function is assumed to define a total ordering.
type family InsertBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: a) (a :: [a]) :: [a] where ... #
sInsertBy :: forall t t t. Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply InsertBySym0 t) t) t :: [a]) #
type family MaximumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
MaximumBy _z_6989586621680000897 '[] = Apply ErrorSym0 "Data.Singletons.List.maximumBy: empty list" | |
MaximumBy cmp ((:) wild_6989586621679997615 wild_6989586621679997617) = Apply (Apply Foldl1Sym0 (Let6989586621680000916MaxBySym3 cmp wild_6989586621679997615 wild_6989586621679997617)) (Let6989586621680000903XsSym3 cmp wild_6989586621679997615 wild_6989586621679997617) |
sMaximumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) #
type family MinimumBy (a :: TyFun a (TyFun a Ordering -> Type) -> Type) (a :: [a]) :: a where ... #
Equations
MinimumBy _z_6989586621680000984 '[] = Apply ErrorSym0 "Data.Singletons.List.minimumBy: empty list" | |
MinimumBy cmp ((:) wild_6989586621679997621 wild_6989586621679997623) = Apply (Apply Foldl1Sym0 (Let6989586621680001003MinBySym3 cmp wild_6989586621679997621 wild_6989586621679997623)) (Let6989586621680000990XsSym3 cmp wild_6989586621679997621 wild_6989586621679997623) |
sMinimumBy :: forall t t. Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) #
The "generic
" operations
The prefix `generic
' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a :: [a]) :: i where ... #
Equations
GenericLength '[] = FromInteger 0 | |
GenericLength ((:) _z_6989586621679998437 xs) = Apply (Apply (:+$) (FromInteger 1)) (Apply GenericLengthSym0 xs) |
sGenericLength :: forall t. SNum i => Sing t -> Sing (Apply GenericLengthSym0 t :: i) #
Defunctionalization symbols
data LengthSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997007] Nat -> *) (LengthSym0 a6989586621679997007) # | |
type Apply [a6989586621679997007] Nat (LengthSym0 a6989586621679997007) l0 # | |
type LengthSym1 t = Length t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679703399 b6989586621679703400 -> Type) (TyFun [a6989586621679703399] [b6989586621679703400] -> Type) -> *) (MapSym0 a6989586621679703399 b6989586621679703400) # | |
type Apply (TyFun a6989586621679703399 b6989586621679703400 -> Type) (TyFun [a6989586621679703399] [b6989586621679703400] -> Type) (MapSym0 a6989586621679703399 b6989586621679703400) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679703399 b6989586621679703400 -> Type) -> TyFun [a6989586621679703399] [b6989586621679703400] -> *) (MapSym1 a6989586621679703399 b6989586621679703400) # | |
type Apply [a6989586621679703399] [b6989586621679703400] (MapSym1 a6989586621679703399 b6989586621679703400 l0) l1 # | |
data ReverseSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997119] [a6989586621679997119] -> *) (ReverseSym0 a6989586621679997119) # | |
type Apply [a6989586621679997119] [a6989586621679997119] (ReverseSym0 a6989586621679997119) l0 # | |
type ReverseSym1 t = Reverse t #
data IntersperseSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997118 (TyFun [a6989586621679997118] [a6989586621679997118] -> Type) -> *) (IntersperseSym0 a6989586621679997118) # | |
type Apply a6989586621679997118 (TyFun [a6989586621679997118] [a6989586621679997118] -> Type) (IntersperseSym0 a6989586621679997118) l0 # | |
data IntersperseSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997118 -> TyFun [a6989586621679997118] [a6989586621679997118] -> *) (IntersperseSym1 a6989586621679997118) # | |
type Apply [a6989586621679997118] [a6989586621679997118] (IntersperseSym1 a6989586621679997118 l0) l1 # | |
type IntersperseSym2 t t = Intersperse t t #
data IntercalateSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997117] (TyFun [[a6989586621679997117]] [a6989586621679997117] -> Type) -> *) (IntercalateSym0 a6989586621679997117) # | |
type Apply [a6989586621679997117] (TyFun [[a6989586621679997117]] [a6989586621679997117] -> Type) (IntercalateSym0 a6989586621679997117) l0 # | |
data IntercalateSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679997117] -> TyFun [[a6989586621679997117]] [a6989586621679997117] -> *) (IntercalateSym1 a6989586621679997117) # | |
type Apply [[a6989586621679997117]] [a6989586621679997117] (IntercalateSym1 a6989586621679997117 l0) l1 # | |
type IntercalateSym2 t t = Intercalate t t #
data TransposeSym0 l #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679997005]] [[a6989586621679997005]] -> *) (TransposeSym0 a6989586621679997005) # | |
type Apply [[a6989586621679997005]] [[a6989586621679997005]] (TransposeSym0 a6989586621679997005) l0 # | |
type TransposeSym1 t = Transpose t #
data SubsequencesSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997116] [[a6989586621679997116]] -> *) (SubsequencesSym0 a6989586621679997116) # | |
type Apply [a6989586621679997116] [[a6989586621679997116]] (SubsequencesSym0 a6989586621679997116) l0 # | |
type SubsequencesSym1 t = Subsequences t #
data PermutationsSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997113] [[a6989586621679997113]] -> *) (PermutationsSym0 a6989586621679997113) # | |
type Apply [a6989586621679997113] [[a6989586621679997113]] (PermutationsSym0 a6989586621679997113) l0 # | |
type PermutationsSym1 t = Permutations t #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) (TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> Type) -> *) (FoldlSym0 a6989586621679650485 b6989586621679650486) # | |
type Apply (TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) (TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> Type) (FoldlSym0 a6989586621679650485 b6989586621679650486) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) -> TyFun b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) -> *) (FoldlSym1 a6989586621679650485 b6989586621679650486) # | |
type Apply b6989586621679650486 (TyFun [a6989586621679650485] b6989586621679650486 -> Type) (FoldlSym1 a6989586621679650485 b6989586621679650486 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679650486 (TyFun a6989586621679650485 b6989586621679650486 -> Type) -> Type) -> b6989586621679650486 -> TyFun [a6989586621679650485] b6989586621679650486 -> *) (FoldlSym2 a6989586621679650485 b6989586621679650486) # | |
type Apply [a6989586621679650485] b6989586621679650486 (FoldlSym2 a6989586621679650485 b6989586621679650486 l1 l0) l2 # | |
data Foldl'Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) (TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> Type) -> *) (Foldl'Sym0 a6989586621679997111 b6989586621679997112) # | |
type Apply (TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) (TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> Type) (Foldl'Sym0 a6989586621679997111 b6989586621679997112) l0 # | |
data Foldl'Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) -> TyFun b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) -> *) (Foldl'Sym1 a6989586621679997111 b6989586621679997112) # | |
type Apply b6989586621679997112 (TyFun [a6989586621679997111] b6989586621679997112 -> Type) (Foldl'Sym1 a6989586621679997111 b6989586621679997112 l0) l1 # | |
data Foldl'Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679997112 (TyFun a6989586621679997111 b6989586621679997112 -> Type) -> Type) -> b6989586621679997112 -> TyFun [a6989586621679997111] b6989586621679997112 -> *) (Foldl'Sym2 a6989586621679997111 b6989586621679997112) # | |
type Apply [a6989586621679997111] b6989586621679997112 (Foldl'Sym2 a6989586621679997111 b6989586621679997112 l1 l0) l2 # | |
type Foldl'Sym3 t t t = Foldl' t t t #
data Foldl1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997110 (TyFun a6989586621679997110 a6989586621679997110 -> Type) -> Type) (TyFun [a6989586621679997110] a6989586621679997110 -> Type) -> *) (Foldl1Sym0 a6989586621679997110) # | |
type Apply (TyFun a6989586621679997110 (TyFun a6989586621679997110 a6989586621679997110 -> Type) -> Type) (TyFun [a6989586621679997110] a6989586621679997110 -> Type) (Foldl1Sym0 a6989586621679997110) l0 # | |
data Foldl1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997110 (TyFun a6989586621679997110 a6989586621679997110 -> Type) -> Type) -> TyFun [a6989586621679997110] a6989586621679997110 -> *) (Foldl1Sym1 a6989586621679997110) # | |
type Apply [a6989586621679997110] a6989586621679997110 (Foldl1Sym1 a6989586621679997110 l0) l1 # | |
type Foldl1Sym2 t t = Foldl1 t t #
data Foldl1'Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997109 (TyFun a6989586621679997109 a6989586621679997109 -> Type) -> Type) (TyFun [a6989586621679997109] a6989586621679997109 -> Type) -> *) (Foldl1'Sym0 a6989586621679997109) # | |
type Apply (TyFun a6989586621679997109 (TyFun a6989586621679997109 a6989586621679997109 -> Type) -> Type) (TyFun [a6989586621679997109] a6989586621679997109 -> Type) (Foldl1'Sym0 a6989586621679997109) l0 # | |
data Foldl1'Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997109 (TyFun a6989586621679997109 a6989586621679997109 -> Type) -> Type) -> TyFun [a6989586621679997109] a6989586621679997109 -> *) (Foldl1'Sym1 a6989586621679997109) # | |
type Apply [a6989586621679997109] a6989586621679997109 (Foldl1'Sym1 a6989586621679997109 l0) l1 # | |
type Foldl1'Sym2 t t = Foldl1' t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) (TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> Type) -> *) (FoldrSym0 a6989586621679703401 b6989586621679703402) # | |
type Apply (TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) (TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> Type) (FoldrSym0 a6989586621679703401 b6989586621679703402) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) -> TyFun b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) -> *) (FoldrSym1 a6989586621679703401 b6989586621679703402) # | |
type Apply b6989586621679703402 (TyFun [a6989586621679703401] b6989586621679703402 -> Type) (FoldrSym1 a6989586621679703401 b6989586621679703402 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679703401 (TyFun b6989586621679703402 b6989586621679703402 -> Type) -> Type) -> b6989586621679703402 -> TyFun [a6989586621679703401] b6989586621679703402 -> *) (FoldrSym2 a6989586621679703401 b6989586621679703402) # | |
type Apply [a6989586621679703401] b6989586621679703402 (FoldrSym2 a6989586621679703401 b6989586621679703402 l1 l0) l2 # | |
data Foldr1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997108 (TyFun a6989586621679997108 a6989586621679997108 -> Type) -> Type) (TyFun [a6989586621679997108] a6989586621679997108 -> Type) -> *) (Foldr1Sym0 a6989586621679997108) # | |
type Apply (TyFun a6989586621679997108 (TyFun a6989586621679997108 a6989586621679997108 -> Type) -> Type) (TyFun [a6989586621679997108] a6989586621679997108 -> Type) (Foldr1Sym0 a6989586621679997108) l0 # | |
data Foldr1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997108 (TyFun a6989586621679997108 a6989586621679997108 -> Type) -> Type) -> TyFun [a6989586621679997108] a6989586621679997108 -> *) (Foldr1Sym1 a6989586621679997108) # | |
type Apply [a6989586621679997108] a6989586621679997108 (Foldr1Sym1 a6989586621679997108 l0) l1 # | |
type Foldr1Sym2 t t = Foldr1 t t #
data ConcatSym0 l #
Instances
SuppressUnusedWarnings (TyFun [[a6989586621679997107]] [a6989586621679997107] -> *) (ConcatSym0 a6989586621679997107) # | |
type Apply [[a6989586621679997107]] [a6989586621679997107] (ConcatSym0 a6989586621679997107) l0 # | |
type ConcatSym1 t = Concat t #
data ConcatMapSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997105 [b6989586621679997106] -> Type) (TyFun [a6989586621679997105] [b6989586621679997106] -> Type) -> *) (ConcatMapSym0 a6989586621679997105 b6989586621679997106) # | |
type Apply (TyFun a6989586621679997105 [b6989586621679997106] -> Type) (TyFun [a6989586621679997105] [b6989586621679997106] -> Type) (ConcatMapSym0 a6989586621679997105 b6989586621679997106) l0 # | |
data ConcatMapSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997105 [b6989586621679997106] -> Type) -> TyFun [a6989586621679997105] [b6989586621679997106] -> *) (ConcatMapSym1 a6989586621679997105 b6989586621679997106) # | |
type Apply [a6989586621679997105] [b6989586621679997106] (ConcatMapSym1 a6989586621679997105 b6989586621679997106 l0) l1 # | |
type ConcatMapSym2 t t = ConcatMap t t #
data ProductSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997008] a6989586621679997008 -> *) (ProductSym0 a6989586621679997008) # | |
type Apply [a6989586621679997008] a6989586621679997008 (ProductSym0 a6989586621679997008) l0 # | |
type ProductSym1 t = Product t #
data MaximumSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997018] a6989586621679997018 -> *) (MaximumSym0 a6989586621679997018) # | |
type Apply [a6989586621679997018] a6989586621679997018 (MaximumSym0 a6989586621679997018) l0 # | |
type MaximumSym1 t = Maximum t #
data MinimumSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997017] a6989586621679997017 -> *) (MinimumSym0 a6989586621679997017) # | |
type Apply [a6989586621679997017] a6989586621679997017 (MinimumSym0 a6989586621679997017) l0 # | |
type MinimumSym1 t = Minimum t #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) (TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> Type) -> *) (ScanlSym0 a6989586621679997103 b6989586621679997102) # | |
type Apply (TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) (TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> Type) (ScanlSym0 a6989586621679997103 b6989586621679997102) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) -> TyFun b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) -> *) (ScanlSym1 a6989586621679997103 b6989586621679997102) # | |
type Apply b6989586621679997102 (TyFun [a6989586621679997103] [b6989586621679997102] -> Type) (ScanlSym1 a6989586621679997103 b6989586621679997102 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun b6989586621679997102 (TyFun a6989586621679997103 b6989586621679997102 -> Type) -> Type) -> b6989586621679997102 -> TyFun [a6989586621679997103] [b6989586621679997102] -> *) (ScanlSym2 a6989586621679997103 b6989586621679997102) # | |
type Apply [a6989586621679997103] [b6989586621679997102] (ScanlSym2 a6989586621679997103 b6989586621679997102 l1 l0) l2 # | |
data Scanl1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997101 (TyFun a6989586621679997101 a6989586621679997101 -> Type) -> Type) (TyFun [a6989586621679997101] [a6989586621679997101] -> Type) -> *) (Scanl1Sym0 a6989586621679997101) # | |
type Apply (TyFun a6989586621679997101 (TyFun a6989586621679997101 a6989586621679997101 -> Type) -> Type) (TyFun [a6989586621679997101] [a6989586621679997101] -> Type) (Scanl1Sym0 a6989586621679997101) l0 # | |
data Scanl1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997101 (TyFun a6989586621679997101 a6989586621679997101 -> Type) -> Type) -> TyFun [a6989586621679997101] [a6989586621679997101] -> *) (Scanl1Sym1 a6989586621679997101) # | |
type Apply [a6989586621679997101] [a6989586621679997101] (Scanl1Sym1 a6989586621679997101 l0) l1 # | |
type Scanl1Sym2 t t = Scanl1 t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) (TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> Type) -> *) (ScanrSym0 a6989586621679997099 b6989586621679997100) # | |
type Apply (TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) (TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> Type) (ScanrSym0 a6989586621679997099 b6989586621679997100) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) -> TyFun b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) -> *) (ScanrSym1 a6989586621679997099 b6989586621679997100) # | |
type Apply b6989586621679997100 (TyFun [a6989586621679997099] [b6989586621679997100] -> Type) (ScanrSym1 a6989586621679997099 b6989586621679997100 l0) l1 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997099 (TyFun b6989586621679997100 b6989586621679997100 -> Type) -> Type) -> b6989586621679997100 -> TyFun [a6989586621679997099] [b6989586621679997100] -> *) (ScanrSym2 a6989586621679997099 b6989586621679997100) # | |
type Apply [a6989586621679997099] [b6989586621679997100] (ScanrSym2 a6989586621679997099 b6989586621679997100 l1 l0) l2 # | |
data Scanr1Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997098 (TyFun a6989586621679997098 a6989586621679997098 -> Type) -> Type) (TyFun [a6989586621679997098] [a6989586621679997098] -> Type) -> *) (Scanr1Sym0 a6989586621679997098) # | |
type Apply (TyFun a6989586621679997098 (TyFun a6989586621679997098 a6989586621679997098 -> Type) -> Type) (TyFun [a6989586621679997098] [a6989586621679997098] -> Type) (Scanr1Sym0 a6989586621679997098) l0 # | |
data Scanr1Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997098 (TyFun a6989586621679997098 a6989586621679997098 -> Type) -> Type) -> TyFun [a6989586621679997098] [a6989586621679997098] -> *) (Scanr1Sym1 a6989586621679997098) # | |
type Apply [a6989586621679997098] [a6989586621679997098] (Scanr1Sym1 a6989586621679997098 l0) l1 # | |
type Scanr1Sym2 t t = Scanr1 t t #
data MapAccumLSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) (TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> Type) -> *) (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # | |
type Apply (TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) (TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> Type) (MapAccumLSym0 x6989586621679997096 acc6989586621679997095 y6989586621679997097) l0 # | |
data MapAccumLSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) -> TyFun acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) -> *) (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # | |
type Apply acc6989586621679997095 (TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> Type) (MapAccumLSym1 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l0) l1 # | |
data MapAccumLSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679997095 (TyFun x6989586621679997096 (acc6989586621679997095, y6989586621679997097) -> Type) -> Type) -> acc6989586621679997095 -> TyFun [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) -> *) (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097) # | |
type Apply [x6989586621679997096] (acc6989586621679997095, [y6989586621679997097]) (MapAccumLSym2 x6989586621679997096 acc6989586621679997095 y6989586621679997097 l1 l0) l2 # | |
type MapAccumLSym3 t t t = MapAccumL t t t #
data MapAccumRSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) (TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> Type) -> *) (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # | |
type Apply (TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) (TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> Type) (MapAccumRSym0 x6989586621679997093 acc6989586621679997092 y6989586621679997094) l0 # | |
data MapAccumRSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) -> TyFun acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) -> *) (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # | |
type Apply acc6989586621679997092 (TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> Type) (MapAccumRSym1 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l0) l1 # | |
data MapAccumRSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun acc6989586621679997092 (TyFun x6989586621679997093 (acc6989586621679997092, y6989586621679997094) -> Type) -> Type) -> acc6989586621679997092 -> TyFun [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) -> *) (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094) # | |
type Apply [x6989586621679997093] (acc6989586621679997092, [y6989586621679997094]) (MapAccumRSym2 x6989586621679997093 acc6989586621679997092 y6989586621679997094 l1 l0) l2 # | |
type MapAccumRSym3 t t t = MapAccumR t t t #
data ReplicateSym0 l #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun a6989586621679997006 [a6989586621679997006] -> Type) -> *) (ReplicateSym0 a6989586621679997006) # | |
type Apply Nat (TyFun a6989586621679997006 [a6989586621679997006] -> Type) (ReplicateSym0 a6989586621679997006) l0 # | |
data ReplicateSym1 l l #
Instances
SuppressUnusedWarnings (Nat -> TyFun a6989586621679997006 [a6989586621679997006] -> *) (ReplicateSym1 a6989586621679997006) # | |
type Apply a6989586621679997006 [a6989586621679997006] (ReplicateSym1 a6989586621679997006 l0) l1 # | |
type ReplicateSym2 t t = Replicate t t #
data UnfoldrSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) (TyFun b6989586621679997090 [a6989586621679997091] -> Type) -> *) (UnfoldrSym0 b6989586621679997090 a6989586621679997091) # | |
type Apply (TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) (TyFun b6989586621679997090 [a6989586621679997091] -> Type) (UnfoldrSym0 b6989586621679997090 a6989586621679997091) l0 # | |
data UnfoldrSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun b6989586621679997090 (Maybe (a6989586621679997091, b6989586621679997090)) -> Type) -> TyFun b6989586621679997090 [a6989586621679997091] -> *) (UnfoldrSym1 a6989586621679997091 b6989586621679997090) # | |
type Apply b6989586621679997090 [a6989586621679997091] (UnfoldrSym1 a6989586621679997091 b6989586621679997090 l0) l1 # | |
type UnfoldrSym2 t t = Unfoldr t t #
data SplitAtSym0 l #
Instances
SuppressUnusedWarnings (TyFun Nat (TyFun [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) -> Type) -> *) (SplitAtSym0 a6989586621679997020) # | |
type Apply Nat (TyFun [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) -> Type) (SplitAtSym0 a6989586621679997020) l0 # | |
data SplitAtSym1 l l #
Instances
SuppressUnusedWarnings (Nat -> TyFun [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) -> *) (SplitAtSym1 a6989586621679997020) # | |
type Apply [a6989586621679997020] ([a6989586621679997020], [a6989586621679997020]) (SplitAtSym1 a6989586621679997020 l0) l1 # | |
type SplitAtSym2 t t = SplitAt t t #
data TakeWhileSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997027 Bool -> Type) (TyFun [a6989586621679997027] [a6989586621679997027] -> Type) -> *) (TakeWhileSym0 a6989586621679997027) # | |
type Apply (TyFun a6989586621679997027 Bool -> Type) (TyFun [a6989586621679997027] [a6989586621679997027] -> Type) (TakeWhileSym0 a6989586621679997027) l0 # | |
data TakeWhileSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997027 Bool -> Type) -> TyFun [a6989586621679997027] [a6989586621679997027] -> *) (TakeWhileSym1 a6989586621679997027) # | |
type Apply [a6989586621679997027] [a6989586621679997027] (TakeWhileSym1 a6989586621679997027 l0) l1 # | |
type TakeWhileSym2 t t = TakeWhile t t #
data DropWhileSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997026 Bool -> Type) (TyFun [a6989586621679997026] [a6989586621679997026] -> Type) -> *) (DropWhileSym0 a6989586621679997026) # | |
type Apply (TyFun a6989586621679997026 Bool -> Type) (TyFun [a6989586621679997026] [a6989586621679997026] -> Type) (DropWhileSym0 a6989586621679997026) l0 # | |
data DropWhileSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997026 Bool -> Type) -> TyFun [a6989586621679997026] [a6989586621679997026] -> *) (DropWhileSym1 a6989586621679997026) # | |
type Apply [a6989586621679997026] [a6989586621679997026] (DropWhileSym1 a6989586621679997026 l0) l1 # | |
type DropWhileSym2 t t = DropWhile t t #
data DropWhileEndSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997025 Bool -> Type) (TyFun [a6989586621679997025] [a6989586621679997025] -> Type) -> *) (DropWhileEndSym0 a6989586621679997025) # | |
type Apply (TyFun a6989586621679997025 Bool -> Type) (TyFun [a6989586621679997025] [a6989586621679997025] -> Type) (DropWhileEndSym0 a6989586621679997025) l0 # | |
data DropWhileEndSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997025 Bool -> Type) -> TyFun [a6989586621679997025] [a6989586621679997025] -> *) (DropWhileEndSym1 a6989586621679997025) # | |
type Apply [a6989586621679997025] [a6989586621679997025] (DropWhileEndSym1 a6989586621679997025 l0) l1 # | |
type DropWhileEndSym2 t t = DropWhileEnd t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997024 Bool -> Type) (TyFun [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) -> Type) -> *) (SpanSym0 a6989586621679997024) # | |
type Apply (TyFun a6989586621679997024 Bool -> Type) (TyFun [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) -> Type) (SpanSym0 a6989586621679997024) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997024 Bool -> Type) -> TyFun [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) -> *) (SpanSym1 a6989586621679997024) # | |
type Apply [a6989586621679997024] ([a6989586621679997024], [a6989586621679997024]) (SpanSym1 a6989586621679997024 l0) l1 # | |
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997023 Bool -> Type) (TyFun [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) -> Type) -> *) (BreakSym0 a6989586621679997023) # | |
type Apply (TyFun a6989586621679997023 Bool -> Type) (TyFun [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) -> Type) (BreakSym0 a6989586621679997023) l0 # | |
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997023 Bool -> Type) -> TyFun [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) -> *) (BreakSym1 a6989586621679997023) # | |
type Apply [a6989586621679997023] ([a6989586621679997023], [a6989586621679997023]) (BreakSym1 a6989586621679997023 l0) l1 # | |
data IsPrefixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997087] (TyFun [a6989586621679997087] Bool -> Type) -> *) (IsPrefixOfSym0 a6989586621679997087) # | |
type Apply [a6989586621679997087] (TyFun [a6989586621679997087] Bool -> Type) (IsPrefixOfSym0 a6989586621679997087) l0 # | |
data IsPrefixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679997087] -> TyFun [a6989586621679997087] Bool -> *) (IsPrefixOfSym1 a6989586621679997087) # | |
type Apply [a6989586621679997087] Bool (IsPrefixOfSym1 a6989586621679997087 l0) l1 # | |
type IsPrefixOfSym2 t t = IsPrefixOf t t #
data IsSuffixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997086] (TyFun [a6989586621679997086] Bool -> Type) -> *) (IsSuffixOfSym0 a6989586621679997086) # | |
type Apply [a6989586621679997086] (TyFun [a6989586621679997086] Bool -> Type) (IsSuffixOfSym0 a6989586621679997086) l0 # | |
data IsSuffixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679997086] -> TyFun [a6989586621679997086] Bool -> *) (IsSuffixOfSym1 a6989586621679997086) # | |
type Apply [a6989586621679997086] Bool (IsSuffixOfSym1 a6989586621679997086 l0) l1 # | |
type IsSuffixOfSym2 t t = IsSuffixOf t t #
data IsInfixOfSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997085] (TyFun [a6989586621679997085] Bool -> Type) -> *) (IsInfixOfSym0 a6989586621679997085) # | |
type Apply [a6989586621679997085] (TyFun [a6989586621679997085] Bool -> Type) (IsInfixOfSym0 a6989586621679997085) l0 # | |
data IsInfixOfSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679997085] -> TyFun [a6989586621679997085] Bool -> *) (IsInfixOfSym1 a6989586621679997085) # | |
type Apply [a6989586621679997085] Bool (IsInfixOfSym1 a6989586621679997085 l0) l1 # | |
type IsInfixOfSym2 t t = IsInfixOf t t #
data NotElemSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997083 (TyFun [a6989586621679997083] Bool -> Type) -> *) (NotElemSym0 a6989586621679997083) # | |
type Apply a6989586621679997083 (TyFun [a6989586621679997083] Bool -> Type) (NotElemSym0 a6989586621679997083) l0 # | |
data NotElemSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997083 -> TyFun [a6989586621679997083] Bool -> *) (NotElemSym1 a6989586621679997083) # | |
type Apply [a6989586621679997083] Bool (NotElemSym1 a6989586621679997083 l0) l1 # | |
type NotElemSym2 t t = NotElem t t #
data LookupSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997012 (TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> Type) -> *) (LookupSym0 a6989586621679997012 b6989586621679997013) # | |
type Apply a6989586621679997012 (TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> Type) (LookupSym0 a6989586621679997012 b6989586621679997013) l0 # | |
data LookupSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997012 -> TyFun [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) -> *) (LookupSym1 b6989586621679997013 a6989586621679997012) # | |
type Apply [(a6989586621679997012, b6989586621679997013)] (Maybe b6989586621679997013) (LookupSym1 b6989586621679997013 a6989586621679997012 l0) l1 # | |
type LookupSym2 t t = Lookup t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997034 Bool -> Type) (TyFun [a6989586621679997034] (Maybe a6989586621679997034) -> Type) -> *) (FindSym0 a6989586621679997034) # | |
type Apply (TyFun a6989586621679997034 Bool -> Type) (TyFun [a6989586621679997034] (Maybe a6989586621679997034) -> Type) (FindSym0 a6989586621679997034) l0 # | |
data FilterSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997035 Bool -> Type) (TyFun [a6989586621679997035] [a6989586621679997035] -> Type) -> *) (FilterSym0 a6989586621679997035) # | |
type Apply (TyFun a6989586621679997035 Bool -> Type) (TyFun [a6989586621679997035] [a6989586621679997035] -> Type) (FilterSym0 a6989586621679997035) l0 # | |
data FilterSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997035 Bool -> Type) -> TyFun [a6989586621679997035] [a6989586621679997035] -> *) (FilterSym1 a6989586621679997035) # | |
type Apply [a6989586621679997035] [a6989586621679997035] (FilterSym1 a6989586621679997035 l0) l1 # | |
type FilterSym2 t t = Filter t t #
data PartitionSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997011 Bool -> Type) (TyFun [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) -> Type) -> *) (PartitionSym0 a6989586621679997011) # | |
type Apply (TyFun a6989586621679997011 Bool -> Type) (TyFun [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) -> Type) (PartitionSym0 a6989586621679997011) l0 # | |
data PartitionSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997011 Bool -> Type) -> TyFun [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) -> *) (PartitionSym1 a6989586621679997011) # | |
type Apply [a6989586621679997011] ([a6989586621679997011], [a6989586621679997011]) (PartitionSym1 a6989586621679997011 l0) l1 # | |
type PartitionSym2 t t = Partition t t #
data ElemIndexSym0 l #
data ElemIndexSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997033 -> TyFun [a6989586621679997033] (Maybe Nat) -> *) (ElemIndexSym1 a6989586621679997033) # | |
type Apply [a6989586621679997033] (Maybe Nat) (ElemIndexSym1 a6989586621679997033 l0) l1 # | |
type ElemIndexSym2 t t = ElemIndex t t #
data ElemIndicesSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997032 (TyFun [a6989586621679997032] [Nat] -> Type) -> *) (ElemIndicesSym0 a6989586621679997032) # | |
type Apply a6989586621679997032 (TyFun [a6989586621679997032] [Nat] -> Type) (ElemIndicesSym0 a6989586621679997032) l0 # | |
data ElemIndicesSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997032 -> TyFun [a6989586621679997032] [Nat] -> *) (ElemIndicesSym1 a6989586621679997032) # | |
type Apply [a6989586621679997032] [Nat] (ElemIndicesSym1 a6989586621679997032 l0) l1 # | |
type ElemIndicesSym2 t t = ElemIndices t t #
data FindIndexSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997031 Bool -> Type) (TyFun [a6989586621679997031] (Maybe Nat) -> Type) -> *) (FindIndexSym0 a6989586621679997031) # | |
type Apply (TyFun a6989586621679997031 Bool -> Type) (TyFun [a6989586621679997031] (Maybe Nat) -> Type) (FindIndexSym0 a6989586621679997031) l0 # | |
data FindIndexSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997031 Bool -> Type) -> TyFun [a6989586621679997031] (Maybe Nat) -> *) (FindIndexSym1 a6989586621679997031) # | |
type Apply [a6989586621679997031] (Maybe Nat) (FindIndexSym1 a6989586621679997031 l0) l1 # | |
type FindIndexSym2 t t = FindIndex t t #
data FindIndicesSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997030 Bool -> Type) (TyFun [a6989586621679997030] [Nat] -> Type) -> *) (FindIndicesSym0 a6989586621679997030) # | |
type Apply (TyFun a6989586621679997030 Bool -> Type) (TyFun [a6989586621679997030] [Nat] -> Type) (FindIndicesSym0 a6989586621679997030) l0 # | |
data FindIndicesSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997030 Bool -> Type) -> TyFun [a6989586621679997030] [Nat] -> *) (FindIndicesSym1 a6989586621679997030) # | |
type Apply [a6989586621679997030] [Nat] (FindIndicesSym1 a6989586621679997030 l0) l1 # | |
type FindIndicesSym2 t t = FindIndices t t #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997081] (TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> Type) -> *) (ZipSym0 a6989586621679997081 b6989586621679997082) # | |
type Apply [a6989586621679997081] (TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> Type) (ZipSym0 a6989586621679997081 b6989586621679997082) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679997081] -> TyFun [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] -> *) (ZipSym1 b6989586621679997082 a6989586621679997081) # | |
type Apply [b6989586621679997082] [(a6989586621679997081, b6989586621679997082)] (ZipSym1 b6989586621679997082 a6989586621679997081 l0) l1 # | |
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997078] (TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> Type) -> *) (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) # | |
type Apply [a6989586621679997078] (TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> Type) (Zip3Sym0 a6989586621679997078 b6989586621679997079 c6989586621679997080) l0 # | |
Instances
SuppressUnusedWarnings ([a6989586621679997078] -> TyFun [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) -> *) (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078) # | |
type Apply [b6989586621679997079] (TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> Type) (Zip3Sym1 b6989586621679997079 c6989586621679997080 a6989586621679997078 l0) l1 # | |
Instances
SuppressUnusedWarnings ([a6989586621679997078] -> [b6989586621679997079] -> TyFun [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] -> *) (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078) # | |
type Apply [c6989586621679997080] [(a6989586621679997078, b6989586621679997079, c6989586621679997080)] (Zip3Sym2 c6989586621679997080 b6989586621679997079 a6989586621679997078 l1 l0) l2 # | |
data ZipWithSym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) (TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> Type) -> *) (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) # | |
type Apply (TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) (TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> Type) (ZipWithSym0 a6989586621679997075 b6989586621679997076 c6989586621679997077) l0 # | |
data ZipWithSym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) -> TyFun [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) -> *) (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077) # | |
type Apply [a6989586621679997075] (TyFun [b6989586621679997076] [c6989586621679997077] -> Type) (ZipWithSym1 a6989586621679997075 b6989586621679997076 c6989586621679997077 l0) l1 # | |
data ZipWithSym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997075 (TyFun b6989586621679997076 c6989586621679997077 -> Type) -> Type) -> [a6989586621679997075] -> TyFun [b6989586621679997076] [c6989586621679997077] -> *) (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077) # | |
type Apply [b6989586621679997076] [c6989586621679997077] (ZipWithSym2 a6989586621679997075 b6989586621679997076 c6989586621679997077 l1 l0) l2 # | |
type ZipWithSym3 t t t = ZipWith t t t #
data ZipWith3Sym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) (TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> Type) -> *) (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # | |
type Apply (TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) (TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> Type) (ZipWith3Sym0 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) l0 # | |
data ZipWith3Sym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> TyFun [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) -> *) (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # | |
type Apply [a6989586621679997071] (TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> Type) (ZipWith3Sym1 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l0) l1 # | |
data ZipWith3Sym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> [a6989586621679997071] -> TyFun [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) -> *) (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # | |
type Apply [b6989586621679997072] (TyFun [c6989586621679997073] [d6989586621679997074] -> Type) (ZipWith3Sym2 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l1 l0) l2 # | |
data ZipWith3Sym3 l l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997071 (TyFun b6989586621679997072 (TyFun c6989586621679997073 d6989586621679997074 -> Type) -> Type) -> Type) -> [a6989586621679997071] -> [b6989586621679997072] -> TyFun [c6989586621679997073] [d6989586621679997074] -> *) (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074) # | |
type Apply [c6989586621679997073] [d6989586621679997074] (ZipWith3Sym3 a6989586621679997071 b6989586621679997072 c6989586621679997073 d6989586621679997074 l2 l1 l0) l3 # | |
type ZipWith3Sym4 t t t t = ZipWith3 t t t t #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997069, b6989586621679997070)] ([a6989586621679997069], [b6989586621679997070]) -> *) (UnzipSym0 a6989586621679997069 b6989586621679997070) # | |
type Apply [(a6989586621679997069, b6989586621679997070)] ([a6989586621679997069], [b6989586621679997070]) (UnzipSym0 a6989586621679997069 b6989586621679997070) l0 # | |
data Unzip3Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997066, b6989586621679997067, c6989586621679997068)] ([a6989586621679997066], [b6989586621679997067], [c6989586621679997068]) -> *) (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) # | |
type Apply [(a6989586621679997066, b6989586621679997067, c6989586621679997068)] ([a6989586621679997066], [b6989586621679997067], [c6989586621679997068]) (Unzip3Sym0 a6989586621679997066 b6989586621679997067 c6989586621679997068) l0 # | |
type Unzip3Sym1 t = Unzip3 t #
data Unzip4Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997062, b6989586621679997063, c6989586621679997064, d6989586621679997065)] ([a6989586621679997062], [b6989586621679997063], [c6989586621679997064], [d6989586621679997065]) -> *) (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) # | |
type Apply [(a6989586621679997062, b6989586621679997063, c6989586621679997064, d6989586621679997065)] ([a6989586621679997062], [b6989586621679997063], [c6989586621679997064], [d6989586621679997065]) (Unzip4Sym0 a6989586621679997062 b6989586621679997063 c6989586621679997064 d6989586621679997065) l0 # | |
type Unzip4Sym1 t = Unzip4 t #
data Unzip5Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997057, b6989586621679997058, c6989586621679997059, d6989586621679997060, e6989586621679997061)] ([a6989586621679997057], [b6989586621679997058], [c6989586621679997059], [d6989586621679997060], [e6989586621679997061]) -> *) (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) # | |
type Apply [(a6989586621679997057, b6989586621679997058, c6989586621679997059, d6989586621679997060, e6989586621679997061)] ([a6989586621679997057], [b6989586621679997058], [c6989586621679997059], [d6989586621679997060], [e6989586621679997061]) (Unzip5Sym0 a6989586621679997057 b6989586621679997058 c6989586621679997059 d6989586621679997060 e6989586621679997061) l0 # | |
type Unzip5Sym1 t = Unzip5 t #
data Unzip6Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997051, b6989586621679997052, c6989586621679997053, d6989586621679997054, e6989586621679997055, f6989586621679997056)] ([a6989586621679997051], [b6989586621679997052], [c6989586621679997053], [d6989586621679997054], [e6989586621679997055], [f6989586621679997056]) -> *) (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) # | |
type Apply [(a6989586621679997051, b6989586621679997052, c6989586621679997053, d6989586621679997054, e6989586621679997055, f6989586621679997056)] ([a6989586621679997051], [b6989586621679997052], [c6989586621679997053], [d6989586621679997054], [e6989586621679997055], [f6989586621679997056]) (Unzip6Sym0 a6989586621679997051 b6989586621679997052 c6989586621679997053 d6989586621679997054 e6989586621679997055 f6989586621679997056) l0 # | |
type Unzip6Sym1 t = Unzip6 t #
data Unzip7Sym0 l #
Instances
SuppressUnusedWarnings (TyFun [(a6989586621679997044, b6989586621679997045, c6989586621679997046, d6989586621679997047, e6989586621679997048, f6989586621679997049, g6989586621679997050)] ([a6989586621679997044], [b6989586621679997045], [c6989586621679997046], [d6989586621679997047], [e6989586621679997048], [f6989586621679997049], [g6989586621679997050]) -> *) (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) # | |
type Apply [(a6989586621679997044, b6989586621679997045, c6989586621679997046, d6989586621679997047, e6989586621679997048, f6989586621679997049, g6989586621679997050)] ([a6989586621679997044], [b6989586621679997045], [c6989586621679997046], [d6989586621679997047], [e6989586621679997048], [f6989586621679997049], [g6989586621679997050]) (Unzip7Sym0 a6989586621679997044 b6989586621679997045 c6989586621679997046 d6989586621679997047 e6989586621679997048 f6989586621679997049 g6989586621679997050) l0 # | |
type Unzip7Sym1 t = Unzip7 t #
data DeleteSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997043 (TyFun [a6989586621679997043] [a6989586621679997043] -> Type) -> *) (DeleteSym0 a6989586621679997043) # | |
type Apply a6989586621679997043 (TyFun [a6989586621679997043] [a6989586621679997043] -> Type) (DeleteSym0 a6989586621679997043) l0 # | |
data DeleteSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997043 -> TyFun [a6989586621679997043] [a6989586621679997043] -> *) (DeleteSym1 a6989586621679997043) # | |
type Apply [a6989586621679997043] [a6989586621679997043] (DeleteSym1 a6989586621679997043 l0) l1 # | |
type DeleteSym2 t t = Delete t t #
data IntersectSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679997029] (TyFun [a6989586621679997029] [a6989586621679997029] -> Type) -> *) (IntersectSym0 a6989586621679997029) # | |
type Apply [a6989586621679997029] (TyFun [a6989586621679997029] [a6989586621679997029] -> Type) (IntersectSym0 a6989586621679997029) l0 # | |
data IntersectSym1 l l #
Instances
SuppressUnusedWarnings ([a6989586621679997029] -> TyFun [a6989586621679997029] [a6989586621679997029] -> *) (IntersectSym1 a6989586621679997029) # | |
type Apply [a6989586621679997029] [a6989586621679997029] (IntersectSym1 a6989586621679997029 l0) l1 # | |
type IntersectSym2 t t = Intersect t t #
data InsertSym0 l #
Instances
SuppressUnusedWarnings (TyFun a6989586621679997016 (TyFun [a6989586621679997016] [a6989586621679997016] -> Type) -> *) (InsertSym0 a6989586621679997016) # | |
type Apply a6989586621679997016 (TyFun [a6989586621679997016] [a6989586621679997016] -> Type) (InsertSym0 a6989586621679997016) l0 # | |
data InsertSym1 l l #
Instances
SuppressUnusedWarnings (a6989586621679997016 -> TyFun [a6989586621679997016] [a6989586621679997016] -> *) (InsertSym1 a6989586621679997016) # | |
type Apply [a6989586621679997016] [a6989586621679997016] (InsertSym1 a6989586621679997016 l0) l1 # | |
type InsertSym2 t t = Insert t t #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997002 (TyFun a6989586621679997002 Bool -> Type) -> Type) (TyFun [a6989586621679997002] [a6989586621679997002] -> Type) -> *) (NubBySym0 a6989586621679997002) # | |
type Apply (TyFun a6989586621679997002 (TyFun a6989586621679997002 Bool -> Type) -> Type) (TyFun [a6989586621679997002] [a6989586621679997002] -> Type) (NubBySym0 a6989586621679997002) l0 # | |
Instances
data DeleteBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) (TyFun a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) -> Type) -> *) (DeleteBySym0 a6989586621679997041) # | |
type Apply (TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) (TyFun a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) -> Type) (DeleteBySym0 a6989586621679997041) l0 # | |
data DeleteBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) -> TyFun a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) -> *) (DeleteBySym1 a6989586621679997041) # | |
type Apply a6989586621679997041 (TyFun [a6989586621679997041] [a6989586621679997041] -> Type) (DeleteBySym1 a6989586621679997041 l0) l1 # | |
data DeleteBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997041 (TyFun a6989586621679997041 Bool -> Type) -> Type) -> a6989586621679997041 -> TyFun [a6989586621679997041] [a6989586621679997041] -> *) (DeleteBySym2 a6989586621679997041) # | |
type Apply [a6989586621679997041] [a6989586621679997041] (DeleteBySym2 a6989586621679997041 l1 l0) l2 # | |
type DeleteBySym3 t t t = DeleteBy t t t #
data DeleteFirstsBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) (TyFun [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) -> Type) -> *) (DeleteFirstsBySym0 a6989586621679997040) # | |
type Apply (TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) (TyFun [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) -> Type) (DeleteFirstsBySym0 a6989586621679997040) l0 # | |
data DeleteFirstsBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) -> TyFun [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) -> *) (DeleteFirstsBySym1 a6989586621679997040) # | |
type Apply [a6989586621679997040] (TyFun [a6989586621679997040] [a6989586621679997040] -> Type) (DeleteFirstsBySym1 a6989586621679997040 l0) l1 # | |
data DeleteFirstsBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997040 (TyFun a6989586621679997040 Bool -> Type) -> Type) -> [a6989586621679997040] -> TyFun [a6989586621679997040] [a6989586621679997040] -> *) (DeleteFirstsBySym2 a6989586621679997040) # | |
type Apply [a6989586621679997040] [a6989586621679997040] (DeleteFirstsBySym2 a6989586621679997040 l1 l0) l2 # | |
type DeleteFirstsBySym3 t t t = DeleteFirstsBy t t t #
data UnionBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) (TyFun [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) -> Type) -> *) (UnionBySym0 a6989586621679997000) # | |
type Apply (TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) (TyFun [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) -> Type) (UnionBySym0 a6989586621679997000) l0 # | |
data UnionBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) -> TyFun [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) -> *) (UnionBySym1 a6989586621679997000) # | |
type Apply [a6989586621679997000] (TyFun [a6989586621679997000] [a6989586621679997000] -> Type) (UnionBySym1 a6989586621679997000 l0) l1 # | |
data UnionBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997000 (TyFun a6989586621679997000 Bool -> Type) -> Type) -> [a6989586621679997000] -> TyFun [a6989586621679997000] [a6989586621679997000] -> *) (UnionBySym2 a6989586621679997000) # | |
type Apply [a6989586621679997000] [a6989586621679997000] (UnionBySym2 a6989586621679997000 l1 l0) l2 # | |
type UnionBySym3 t t t = UnionBy t t t #
data IntersectBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) (TyFun [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) -> Type) -> *) (IntersectBySym0 a6989586621679997028) # | |
type Apply (TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) (TyFun [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) -> Type) (IntersectBySym0 a6989586621679997028) l0 # | |
data IntersectBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) -> TyFun [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) -> *) (IntersectBySym1 a6989586621679997028) # | |
type Apply [a6989586621679997028] (TyFun [a6989586621679997028] [a6989586621679997028] -> Type) (IntersectBySym1 a6989586621679997028 l0) l1 # | |
data IntersectBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997028 (TyFun a6989586621679997028 Bool -> Type) -> Type) -> [a6989586621679997028] -> TyFun [a6989586621679997028] [a6989586621679997028] -> *) (IntersectBySym2 a6989586621679997028) # | |
type Apply [a6989586621679997028] [a6989586621679997028] (IntersectBySym2 a6989586621679997028 l1 l0) l2 # | |
type IntersectBySym3 t t t = IntersectBy t t t #
data GroupBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997014 (TyFun a6989586621679997014 Bool -> Type) -> Type) (TyFun [a6989586621679997014] [[a6989586621679997014]] -> Type) -> *) (GroupBySym0 a6989586621679997014) # | |
type Apply (TyFun a6989586621679997014 (TyFun a6989586621679997014 Bool -> Type) -> Type) (TyFun [a6989586621679997014] [[a6989586621679997014]] -> Type) (GroupBySym0 a6989586621679997014) l0 # | |
data GroupBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997014 (TyFun a6989586621679997014 Bool -> Type) -> Type) -> TyFun [a6989586621679997014] [[a6989586621679997014]] -> *) (GroupBySym1 a6989586621679997014) # | |
type Apply [a6989586621679997014] [[a6989586621679997014]] (GroupBySym1 a6989586621679997014 l0) l1 # | |
type GroupBySym2 t t = GroupBy t t #
data SortBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997039 (TyFun a6989586621679997039 Ordering -> Type) -> Type) (TyFun [a6989586621679997039] [a6989586621679997039] -> Type) -> *) (SortBySym0 a6989586621679997039) # | |
type Apply (TyFun a6989586621679997039 (TyFun a6989586621679997039 Ordering -> Type) -> Type) (TyFun [a6989586621679997039] [a6989586621679997039] -> Type) (SortBySym0 a6989586621679997039) l0 # | |
data SortBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997039 (TyFun a6989586621679997039 Ordering -> Type) -> Type) -> TyFun [a6989586621679997039] [a6989586621679997039] -> *) (SortBySym1 a6989586621679997039) # | |
type Apply [a6989586621679997039] [a6989586621679997039] (SortBySym1 a6989586621679997039 l0) l1 # | |
type SortBySym2 t t = SortBy t t #
data InsertBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) (TyFun a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) -> Type) -> *) (InsertBySym0 a6989586621679997038) # | |
type Apply (TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) (TyFun a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) -> Type) (InsertBySym0 a6989586621679997038) l0 # | |
data InsertBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) -> TyFun a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) -> *) (InsertBySym1 a6989586621679997038) # | |
type Apply a6989586621679997038 (TyFun [a6989586621679997038] [a6989586621679997038] -> Type) (InsertBySym1 a6989586621679997038 l0) l1 # | |
data InsertBySym2 l l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997038 (TyFun a6989586621679997038 Ordering -> Type) -> Type) -> a6989586621679997038 -> TyFun [a6989586621679997038] [a6989586621679997038] -> *) (InsertBySym2 a6989586621679997038) # | |
type Apply [a6989586621679997038] [a6989586621679997038] (InsertBySym2 a6989586621679997038 l1 l0) l2 # | |
type InsertBySym3 t t t = InsertBy t t t #
data MaximumBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997037 (TyFun a6989586621679997037 Ordering -> Type) -> Type) (TyFun [a6989586621679997037] a6989586621679997037 -> Type) -> *) (MaximumBySym0 a6989586621679997037) # | |
type Apply (TyFun a6989586621679997037 (TyFun a6989586621679997037 Ordering -> Type) -> Type) (TyFun [a6989586621679997037] a6989586621679997037 -> Type) (MaximumBySym0 a6989586621679997037) l0 # | |
data MaximumBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997037 (TyFun a6989586621679997037 Ordering -> Type) -> Type) -> TyFun [a6989586621679997037] a6989586621679997037 -> *) (MaximumBySym1 a6989586621679997037) # | |
type Apply [a6989586621679997037] a6989586621679997037 (MaximumBySym1 a6989586621679997037 l0) l1 # | |
type MaximumBySym2 t t = MaximumBy t t #
data MinimumBySym0 l #
Instances
SuppressUnusedWarnings (TyFun (TyFun a6989586621679997036 (TyFun a6989586621679997036 Ordering -> Type) -> Type) (TyFun [a6989586621679997036] a6989586621679997036 -> Type) -> *) (MinimumBySym0 a6989586621679997036) # | |
type Apply (TyFun a6989586621679997036 (TyFun a6989586621679997036 Ordering -> Type) -> Type) (TyFun [a6989586621679997036] a6989586621679997036 -> Type) (MinimumBySym0 a6989586621679997036) l0 # | |
data MinimumBySym1 l l #
Instances
SuppressUnusedWarnings ((TyFun a6989586621679997036 (TyFun a6989586621679997036 Ordering -> Type) -> Type) -> TyFun [a6989586621679997036] a6989586621679997036 -> *) (MinimumBySym1 a6989586621679997036) # | |
type Apply [a6989586621679997036] a6989586621679997036 (MinimumBySym1 a6989586621679997036 l0) l1 # | |
type MinimumBySym2 t t = MinimumBy t t #
data GenericLengthSym0 l #
Instances
SuppressUnusedWarnings (TyFun [a6989586621679996998] i6989586621679996997 -> *) (GenericLengthSym0 a6989586621679996998 i6989586621679996997) # | |
type Apply [a6989586621679996998] k2 (GenericLengthSym0 a6989586621679996998 k2) l0 # | |
type GenericLengthSym1 t = GenericLength t #