| Copyright | (C) 2013-2014 Richard Eisenberg Jan Stolarek |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | GHC2021 |
Data.List.Singletons
Description
Defines functions and datatypes relating to the singleton for '[]',
including singled versions 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.
Synopsis
- type family Sing :: k -> Type
- data SList (a1 :: [a]) where
- type family (a1 :: [a]) ++ (a2 :: [a]) :: [a] where ...
- (%++) :: forall a (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2)
- type family Head (a1 :: [a]) :: a where ...
- sHead :: forall a (t :: [a]). Sing t -> Sing (Apply (HeadSym0 :: TyFun [a] a -> Type) t)
- type family Last (a1 :: [a]) :: a where ...
- sLast :: forall a (t :: [a]). Sing t -> Sing (Apply (LastSym0 :: TyFun [a] a -> Type) t)
- type family Tail (a1 :: [a]) :: [a] where ...
- sTail :: forall a (t :: [a]). Sing t -> Sing (Apply (TailSym0 :: TyFun [a] [a] -> Type) t)
- type family Init (a1 :: [a]) :: [a] where ...
- sInit :: forall a (t :: [a]). Sing t -> Sing (Apply (InitSym0 :: TyFun [a] [a] -> Type) t)
- type family Null (arg :: t a) :: Bool
- sNull :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Apply (NullSym0 :: TyFun (t a) Bool -> Type) t1)
- type family Length (arg :: t a) :: Natural
- sLength :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (t a) Natural -> Type) t1)
- type family Map (a1 :: a ~> b) (a2 :: [a]) :: [b] where ...
- sMap :: forall a b (t1 :: a ~> b) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) t1) t2)
- type family Reverse (a1 :: [a]) :: [a] where ...
- sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply (ReverseSym0 :: TyFun [a] [a] -> Type) t)
- type family Intersperse (a1 :: a) (a2 :: [a]) :: [a] where ...
- sIntersperse :: forall a (t1 :: a) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2)
- type family Intercalate (a1 :: [a]) (a2 :: [[a]]) :: [a] where ...
- sIntercalate :: forall a (t1 :: [a]) (t2 :: [[a]]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) t1) t2)
- type family Transpose (a1 :: [[a]]) :: [[a]] where ...
- sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) t)
- type family Subsequences (a1 :: [a]) :: [[a]] where ...
- sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) t)
- type family Permutations (a1 :: [a]) :: [[a]] where ...
- sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) t)
- type family Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) :: b
- sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3)
- type family Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) :: b
- sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3)
- type family Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a
- sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2)
- type family Foldl1' (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: a where ...
- sFoldl1' :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) t1) t2)
- type family Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: t a) :: b
- sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3)
- type family Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a
- sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2)
- type family Concat (a1 :: t [a]) :: [a] where ...
- sConcat :: forall (t1 :: Type -> Type) a (t2 :: t1 [a]). SFoldable t1 => Sing t2 -> Sing (Apply (ConcatSym0 :: TyFun (t1 [a]) [a] -> Type) t2)
- type family ConcatMap (a1 :: a ~> [b]) (a2 :: t a) :: [b] where ...
- sConcatMap :: forall a b (t1 :: Type -> Type) (t2 :: a ~> [b]) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t1 a ~> [b]) -> Type) t2) t3)
- type family And (a :: t Bool) :: Bool where ...
- sAnd :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (AndSym0 :: TyFun (t1 Bool) Bool -> Type) t2)
- type family Or (a :: t Bool) :: Bool where ...
- sOr :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (OrSym0 :: TyFun (t1 Bool) Bool -> Type) t2)
- type family Any (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ...
- sAny :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AnySym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) t2) t3)
- type family All (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ...
- sAll :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AllSym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) t2) t3)
- type family Sum (arg :: t a) :: a
- sSum :: forall a (t1 :: t a). (SFoldable t, SNum a) => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (t a) a -> Type) t1)
- type family Product (arg :: t a) :: a
- sProduct :: forall a (t1 :: t a). (SFoldable t, SNum a) => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (t a) a -> Type) t1)
- type family Maximum (arg :: t a) :: a
- sMaximum :: forall a (t1 :: t a). (SFoldable t, SOrd a) => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (t a) a -> Type) t1)
- type family Minimum (arg :: t a) :: a
- sMinimum :: forall a (t1 :: t a). (SFoldable t, SOrd a) => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (t a) a -> Type) t1)
- type family Scanl (a1 :: b ~> (a ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ...
- sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) t1) t2) t3)
- type family Scanl1 (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: [a] where ...
- sScanl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) t1) t2)
- type family Scanr (a1 :: a ~> (b ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ...
- sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) t1) t2) t3)
- type family Scanr1 (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: [a] where ...
- sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) t1) t2)
- type family MapAccumL (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ...
- sMapAccumL :: forall (t1 :: Type -> Type) a b c (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t1 b ~> (a, t1 c))) -> Type) t2) t3) t4)
- type family MapAccumR (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ...
- sMapAccumR :: forall a b c (t1 :: Type -> Type) (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t1 b ~> (a, t1 c))) -> Type) t2) t3) t4)
- type family Replicate (a1 :: Natural) (a2 :: a) :: [a] where ...
- sReplicate :: forall a (t1 :: Natural) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) t1) t2)
- type family Unfoldr (a1 :: b ~> Maybe (a, b)) (a2 :: b) :: [a] where ...
- sUnfoldr :: forall b a (t1 :: b ~> Maybe (a, b)) (t2 :: b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) t1) t2)
- type family Take (a1 :: Natural) (a2 :: [a]) :: [a] where ...
- sTake :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) t1) t2)
- type family Drop (a1 :: Natural) (a2 :: [a]) :: [a] where ...
- sDrop :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) t1) t2)
- type family SplitAt (a1 :: Natural) (a2 :: [a]) :: ([a], [a]) where ...
- sSplitAt :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) t1) t2)
- type family TakeWhile (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ...
- sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2)
- type family DropWhile (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ...
- sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2)
- type family DropWhileEnd (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ...
- sDropWhileEnd :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2)
- type family Span (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ...
- sSpan :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2)
- type family Break (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ...
- sBreak :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2)
- type family StripPrefix (a1 :: [a]) (a2 :: [a]) :: Maybe [a] where ...
- type family Group (a1 :: [a]) :: [[a]] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) t)
- type family Inits (a1 :: [a]) :: [[a]] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) t)
- type family Tails (a1 :: [a]) :: [[a]] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) t)
- type family IsPrefixOf (a1 :: [a]) (a2 :: [a]) :: Bool where ...
- sIsPrefixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2)
- type family IsSuffixOf (a1 :: [a]) (a2 :: [a]) :: Bool where ...
- sIsSuffixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2)
- type family IsInfixOf (a1 :: [a]) (a2 :: [a]) :: Bool where ...
- sIsInfixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2)
- type family Elem (arg :: a) (arg1 :: t a) :: Bool
- sElem :: forall a (t1 :: a) (t2 :: t a). (SFoldable t, SEq a) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2)
- type family NotElem (a1 :: a) (a2 :: t a) :: Bool where ...
- sNotElem :: forall a (t1 :: Type -> Type) (t2 :: a) (t3 :: t1 a). (SFoldable t1, SEq a) => Sing t2 -> Sing t3 -> Sing (Apply (Apply (NotElemSym0 :: TyFun a (t1 a ~> Bool) -> Type) t2) t3)
- type family Lookup (a1 :: a) (a2 :: [(a, b)]) :: Maybe b where ...
- sLookup :: forall a b (t1 :: a) (t2 :: [(a, b)]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) t1) t2)
- type family Find (a1 :: a ~> Bool) (a2 :: t a) :: Maybe a where ...
- sFind :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (FindSym0 :: TyFun (a ~> Bool) (t1 a ~> Maybe a) -> Type) t2) t3)
- type family Filter (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ...
- sFilter :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2)
- type family Partition (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ...
- sPartition :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2)
- type family (a1 :: [a]) !! (a2 :: Natural) :: a where ...
- (%!!) :: forall a (t1 :: [a]) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) t1) t2)
- type family ElemIndex (a1 :: a) (a2 :: [a]) :: Maybe Natural where ...
- sElemIndex :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) t1) t2)
- type family ElemIndices (a1 :: a) (a2 :: [a]) :: [Natural] where ...
- sElemIndices :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) t1) t2)
- type family FindIndex (a1 :: a ~> Bool) (a2 :: [a]) :: Maybe Natural where ...
- sFindIndex :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) t1) t2)
- type family FindIndices (a1 :: a ~> Bool) (a2 :: [a]) :: [Natural] where ...
- sFindIndices :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) t1) t2)
- type family Zip (a1 :: [a]) (a2 :: [b]) :: [(a, b)] where ...
- sZip :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) t1) t2)
- type family Zip3 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) :: [(a, b, c)] where ...
- sZip3 :: forall a b c (t1 :: [a]) (t2 :: [b]) (t3 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) t1) t2) t3)
- type family Zip4 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) :: [(a, b, c, d)] where ...
- type family Zip5 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) :: [(a, b, c, d, e)] where ...
- type family Zip6 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) (a6 :: [f]) :: [(a, b, c, d, e, f)] where ...
- type family Zip7 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) (a6 :: [f]) (a7 :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: [a]) (a3 :: [b]) :: [c] where ...
- sZipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) t1) t2) t3)
- type family ZipWith3 (a1 :: a ~> (b ~> (c ~> d))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) :: [d] where ...
- sZipWith3 :: forall a b c d (t1 :: a ~> (b ~> (c ~> d))) (t2 :: [a]) (t3 :: [b]) (t4 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) t1) t2) t3) t4)
- type family ZipWith4 (a1 :: a ~> (b ~> (c ~> (d ~> e)))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) :: [e] where ...
- type family ZipWith5 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) :: [f] where ...
- type family ZipWith6 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) (a7 :: [f]) :: [g] where ...
- type family ZipWith7 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) (a7 :: [f]) (a8 :: [g]) :: [h] where ...
- type family Unzip (a1 :: [(a, b)]) :: ([a], [b]) where ...
- sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) t)
- type family Unzip3 (a1 :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) t)
- type family Unzip4 (a1 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) t)
- type family Unzip5 (a1 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) t)
- type family Unzip6 (a1 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) t)
- type family Unzip7 (a1 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) t)
- type family Unlines (a :: [Symbol]) :: Symbol where ...
- sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnlinesSym0 t)
- type family Unwords (a :: [Symbol]) :: Symbol where ...
- sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 t)
- type family Nub (a1 :: [a]) :: [a] where ...
- sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply (NubSym0 :: TyFun [a] [a] -> Type) t)
- type family Delete (a1 :: a) (a2 :: [a]) :: [a] where ...
- sDelete :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2)
- type family (a1 :: [a]) \\ (a2 :: [a]) :: [a] where ...
- (%\\) :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2)
- type family Union (a1 :: [a]) (a2 :: [a]) :: [a] where ...
- sUnion :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2)
- type family Intersect (a1 :: [a]) (a2 :: [a]) :: [a] where ...
- sIntersect :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2)
- type family Insert (a1 :: a) (a2 :: [a]) :: [a] where ...
- sInsert :: forall a (t1 :: a) (t2 :: [a]). SOrd a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2)
- type family Sort (a1 :: [a]) :: [a] where ...
- sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply (SortSym0 :: TyFun [a] [a] -> Type) t)
- type family NubBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) :: [a] where ...
- sNubBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) t1) t2)
- type family DeleteBy (a1 :: a ~> (a ~> Bool)) (a2 :: a) (a3 :: [a]) :: [a] where ...
- sDeleteBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: a) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) t1) t2) t3)
- type family DeleteFirstsBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ...
- sDeleteFirstsBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3)
- type family UnionBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ...
- sUnionBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3)
- type family IntersectBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ...
- sIntersectBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3)
- type family GroupBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) :: [[a]] where ...
- sGroupBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) t1) t2)
- type family SortBy (a1 :: a ~> (a ~> Ordering)) (a2 :: [a]) :: [a] where ...
- sSortBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) t1) t2)
- type family InsertBy (a1 :: a ~> (a ~> Ordering)) (a2 :: a) (a3 :: [a]) :: [a] where ...
- sInsertBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: a) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) t1) t2) t3)
- type family MaximumBy (a1 :: a ~> (a ~> Ordering)) (a2 :: t a) :: a where ...
- sMaximumBy :: forall a (t1 :: Type -> Type) (t2 :: a ~> (a ~> Ordering)) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t1 a ~> a) -> Type) t2) t3)
- type family MinimumBy (a1 :: a ~> (a ~> Ordering)) (a2 :: t a) :: a where ...
- sMinimumBy :: forall a (t1 :: Type -> Type) (t2 :: a ~> (a ~> Ordering)) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t1 a ~> a) -> Type) t2) t3)
- type family GenericLength (a1 :: [a]) :: i where ...
- sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply (GenericLengthSym0 :: TyFun [a] i -> Type) t)
- type family NilSym0 :: [a] where ...
- data (:@#@$) (a1 :: TyFun a ([a] ~> [a]))
- data (a6989586621679046238 :: a) :@#@$$ (b :: TyFun [a] [a])
- type family (a6989586621679046238 :: a) :@#@$$$ (a6989586621679046239 :: [a]) :: [a] where ...
- type family (a6989586621679180230 :: [a]) ++@#@$$$ (a6989586621679180231 :: [a]) :: [a] where ...
- data (a6989586621679180230 :: [a]) ++@#@$$ (b :: TyFun [a] [a])
- data (++@#@$) (a1 :: TyFun [a] ([a] ~> [a]))
- data HeadSym0 (a1 :: TyFun [a] a)
- type family HeadSym1 (a6989586621679815823 :: [a]) :: a where ...
- data LastSym0 (a1 :: TyFun [a] a)
- type family LastSym1 (a6989586621679815817 :: [a]) :: a where ...
- data TailSym0 (a1 :: TyFun [a] [a])
- type family TailSym1 (a6989586621679815813 :: [a]) :: [a] where ...
- data InitSym0 (a1 :: TyFun [a] [a])
- type family InitSym1 (a6989586621679815801 :: [a]) :: [a] where ...
- data NullSym0 (a1 :: TyFun (t a) Bool)
- type family NullSym1 (a6989586621680390432 :: t a) :: Bool where ...
- data LengthSym0 (a1 :: TyFun (t a) Natural)
- type family LengthSym1 (a6989586621680390435 :: t a) :: Natural where ...
- data MapSym0 (a1 :: TyFun (a ~> b) ([a] ~> [b]))
- data MapSym1 (a6989586621679180239 :: a ~> b) (b1 :: TyFun [a] [b])
- type family MapSym2 (a6989586621679180239 :: a ~> b) (a6989586621679180240 :: [a]) :: [b] where ...
- data ReverseSym0 (a1 :: TyFun [a] [a])
- type family ReverseSym1 (a6989586621679815786 :: [a]) :: [a] where ...
- data IntersperseSym0 (a1 :: TyFun a ([a] ~> [a]))
- data IntersperseSym1 (a6989586621679815779 :: a) (b :: TyFun [a] [a])
- type family IntersperseSym2 (a6989586621679815779 :: a) (a6989586621679815780 :: [a]) :: [a] where ...
- data IntercalateSym0 (a1 :: TyFun [a] ([[a]] ~> [a]))
- data IntercalateSym1 (a6989586621679815772 :: [a]) (b :: TyFun [[a]] [a])
- type family IntercalateSym2 (a6989586621679815772 :: [a]) (a6989586621679815773 :: [[a]]) :: [a] where ...
- data TransposeSym0 (a1 :: TyFun [[a]] [[a]])
- type family TransposeSym1 (a6989586621679814673 :: [[a]]) :: [[a]] where ...
- data SubsequencesSym0 (a1 :: TyFun [a] [[a]])
- type family SubsequencesSym1 (a6989586621679815767 :: [a]) :: [[a]] where ...
- data PermutationsSym0 (a1 :: TyFun [a] [[a]])
- type family PermutationsSym1 (a6989586621679815693 :: [a]) :: [[a]] where ...
- data FoldlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)))
- data FoldlSym1 (a6989586621680390407 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b))
- data FoldlSym2 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (c :: TyFun (t a) b)
- type family FoldlSym3 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (a6989586621680390409 :: t a) :: b where ...
- data Foldl'Sym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)))
- data Foldl'Sym1 (a6989586621680390414 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b))
- data Foldl'Sym2 (a6989586621680390414 :: b ~> (a ~> b)) (a6989586621680390415 :: b) (c :: TyFun (t a) b)
- type family Foldl'Sym3 (a6989586621680390414 :: b ~> (a ~> b)) (a6989586621680390415 :: b) (a6989586621680390416 :: t a) :: b where ...
- data Foldl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a))
- data Foldl1Sym1 (a6989586621680390425 :: a ~> (a ~> a)) (b :: TyFun (t a) a)
- type family Foldl1Sym2 (a6989586621680390425 :: a ~> (a ~> a)) (a6989586621680390426 :: t a) :: a where ...
- data Foldl1'Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> a))
- data Foldl1'Sym1 (a6989586621679815658 :: a ~> (a ~> a)) (b :: TyFun [a] a)
- type family Foldl1'Sym2 (a6989586621679815658 :: a ~> (a ~> a)) (a6989586621679815659 :: [a]) :: a where ...
- data FoldrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)))
- data FoldrSym1 (a6989586621680390393 :: a ~> (b ~> b)) (b1 :: TyFun b (t a ~> b))
- data FoldrSym2 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (c :: TyFun (t a) b)
- type family FoldrSym3 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (a6989586621680390395 :: t a) :: b where ...
- data Foldr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a))
- data Foldr1Sym1 (a6989586621680390420 :: a ~> (a ~> a)) (b :: TyFun (t a) a)
- type family Foldr1Sym2 (a6989586621680390420 :: a ~> (a ~> a)) (a6989586621680390421 :: t a) :: a where ...
- data ConcatSym0 (a1 :: TyFun (t [a]) [a])
- type family ConcatSym1 (a6989586621680390274 :: t [a]) :: [a] where ...
- data ConcatMapSym0 (a1 :: TyFun (a ~> [b]) (t a ~> [b]))
- data ConcatMapSym1 (a6989586621680390263 :: a ~> [b]) (b1 :: TyFun (t a) [b])
- type family ConcatMapSym2 (a6989586621680390263 :: a ~> [b]) (a6989586621680390264 :: t a) :: [b] where ...
- data AndSym0 (a :: TyFun (t Bool) Bool)
- type family AndSym1 (a6989586621680390258 :: t Bool) :: Bool where ...
- data OrSym0 (a :: TyFun (t Bool) Bool)
- type family OrSym1 (a6989586621680390252 :: t Bool) :: Bool where ...
- data AnySym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool))
- data AnySym1 (a6989586621680390244 :: a ~> Bool) (b :: TyFun (t a) Bool)
- type family AnySym2 (a6989586621680390244 :: a ~> Bool) (a6989586621680390245 :: t a) :: Bool where ...
- data AllSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool))
- data AllSym1 (a6989586621680390235 :: a ~> Bool) (b :: TyFun (t a) Bool)
- type family AllSym2 (a6989586621680390235 :: a ~> Bool) (a6989586621680390236 :: t a) :: Bool where ...
- data SumSym0 (a1 :: TyFun (t a) a)
- type family SumSym1 (a6989586621680390449 :: t a) :: a where ...
- data ProductSym0 (a1 :: TyFun (t a) a)
- type family ProductSym1 (a6989586621680390452 :: t a) :: a where ...
- data MaximumSym0 (a1 :: TyFun (t a) a)
- type family MaximumSym1 (a6989586621680390443 :: t a) :: a where ...
- data MinimumSym0 (a1 :: TyFun (t a) a)
- type family MinimumSym1 (a6989586621680390446 :: t a) :: a where ...
- data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])))
- data ScanlSym1 (a6989586621679815591 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> [b]))
- data ScanlSym2 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (c :: TyFun [a] [b])
- type family ScanlSym3 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (a6989586621679815593 :: [a]) :: [b] where ...
- data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]))
- data Scanl1Sym1 (a6989586621679815582 :: a ~> (a ~> a)) (b :: TyFun [a] [a])
- type family Scanl1Sym2 (a6989586621679815582 :: a ~> (a ~> a)) (a6989586621679815583 :: [a]) :: [a] where ...
- data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])))
- data ScanrSym1 (a6989586621679815564 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> [b]))
- data ScanrSym2 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (c :: TyFun [a] [b])
- type family ScanrSym3 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (a6989586621679815566 :: [a]) :: [b] where ...
- data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]))
- data Scanr1Sym1 (a6989586621679815544 :: a ~> (a ~> a)) (b :: TyFun [a] [a])
- type family Scanr1Sym2 (a6989586621679815544 :: a ~> (a ~> a)) (a6989586621679815545 :: [a]) :: [a] where ...
- data MapAccumLSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumLSym1 (a6989586621680741278 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumLSym2 (a6989586621680741278 :: a ~> (b ~> (a, c))) (a6989586621680741279 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumLSym3 (a6989586621680741278 :: a ~> (b ~> (a, c))) (a6989586621680741279 :: a) (a6989586621680741280 :: t b) :: (a, t c) where ...
- data MapAccumRSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumRSym1 (a6989586621680741268 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumRSym2 (a6989586621680741268 :: a ~> (b ~> (a, c))) (a6989586621680741269 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumRSym3 (a6989586621680741268 :: a ~> (b ~> (a, c))) (a6989586621680741269 :: a) (a6989586621680741270 :: t b) :: (a, t c) where ...
- data ReplicateSym0 (a1 :: TyFun Natural (a ~> [a]))
- data ReplicateSym1 (a6989586621679814681 :: Natural) (b :: TyFun a [a])
- type family ReplicateSym2 (a6989586621679814681 :: Natural) (a6989586621679814682 :: a) :: [a] where ...
- data UnfoldrSym0 (a1 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]))
- data UnfoldrSym1 (a6989586621679815436 :: b ~> Maybe (a, b)) (b1 :: TyFun b [a])
- type family UnfoldrSym2 (a6989586621679815436 :: b ~> Maybe (a, b)) (a6989586621679815437 :: b) :: [a] where ...
- data TakeSym0 (a1 :: TyFun Natural ([a] ~> [a]))
- data TakeSym1 (a6989586621679814836 :: Natural) (b :: TyFun [a] [a])
- type family TakeSym2 (a6989586621679814836 :: Natural) (a6989586621679814837 :: [a]) :: [a] where ...
- data DropSym0 (a1 :: TyFun Natural ([a] ~> [a]))
- data DropSym1 (a6989586621679814823 :: Natural) (b :: TyFun [a] [a])
- type family DropSym2 (a6989586621679814823 :: Natural) (a6989586621679814824 :: [a]) :: [a] where ...
- data SplitAtSym0 (a1 :: TyFun Natural ([a] ~> ([a], [a])))
- data SplitAtSym1 (a6989586621679814816 :: Natural) (b :: TyFun [a] ([a], [a]))
- type family SplitAtSym2 (a6989586621679814816 :: Natural) (a6989586621679814817 :: [a]) :: ([a], [a]) where ...
- data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data TakeWhileSym1 (a6989586621679814953 :: a ~> Bool) (b :: TyFun [a] [a])
- type family TakeWhileSym2 (a6989586621679814953 :: a ~> Bool) (a6989586621679814954 :: [a]) :: [a] where ...
- data DropWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data DropWhileSym1 (a6989586621679814938 :: a ~> Bool) (b :: TyFun [a] [a])
- type family DropWhileSym2 (a6989586621679814938 :: a ~> Bool) (a6989586621679814939 :: [a]) :: [a] where ...
- data DropWhileEndSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data DropWhileEndSym1 (a6989586621679814921 :: a ~> Bool) (b :: TyFun [a] [a])
- type family DropWhileEndSym2 (a6989586621679814921 :: a ~> Bool) (a6989586621679814922 :: [a]) :: [a] where ...
- data SpanSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data SpanSym1 (a6989586621679814884 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family SpanSym2 (a6989586621679814884 :: a ~> Bool) (a6989586621679814885 :: [a]) :: ([a], [a]) where ...
- data BreakSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data BreakSym1 (a6989586621679814849 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family BreakSym2 (a6989586621679814849 :: a ~> Bool) (a6989586621679814850 :: [a]) :: ([a], [a]) where ...
- data StripPrefixSym0 (a1 :: TyFun [a] ([a] ~> Maybe [a]))
- data StripPrefixSym1 (a6989586621679966032 :: [a]) (b :: TyFun [a] (Maybe [a]))
- type family StripPrefixSym2 (a6989586621679966032 :: [a]) (a6989586621679966033 :: [a]) :: Maybe [a] where ...
- data GroupSym0 (a1 :: TyFun [a] [[a]])
- type family GroupSym1 (a6989586621679814811 :: [a]) :: [[a]] where ...
- data InitsSym0 (a1 :: TyFun [a] [[a]])
- type family InitsSym1 (a6989586621679815426 :: [a]) :: [[a]] where ...
- data TailsSym0 (a1 :: TyFun [a] [[a]])
- type family TailsSym1 (a6989586621679815418 :: [a]) :: [[a]] where ...
- data IsPrefixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsPrefixOfSym1 (a6989586621679815410 :: [a]) (b :: TyFun [a] Bool)
- type family IsPrefixOfSym2 (a6989586621679815410 :: [a]) (a6989586621679815411 :: [a]) :: Bool where ...
- data IsSuffixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsSuffixOfSym1 (a6989586621679815403 :: [a]) (b :: TyFun [a] Bool)
- type family IsSuffixOfSym2 (a6989586621679815403 :: [a]) (a6989586621679815404 :: [a]) :: Bool where ...
- data IsInfixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsInfixOfSym1 (a6989586621679815396 :: [a]) (b :: TyFun [a] Bool)
- type family IsInfixOfSym2 (a6989586621679815396 :: [a]) (a6989586621679815397 :: [a]) :: Bool where ...
- data ElemSym0 (a1 :: TyFun a (t a ~> Bool))
- data ElemSym1 (a6989586621680390439 :: a) (b :: TyFun (t a) Bool)
- type family ElemSym2 (a6989586621680390439 :: a) (a6989586621680390440 :: t a) :: Bool where ...
- data NotElemSym0 (a1 :: TyFun a (t a ~> Bool))
- data NotElemSym1 (a6989586621680390186 :: a) (b :: TyFun (t a) Bool)
- type family NotElemSym2 (a6989586621680390186 :: a) (a6989586621680390187 :: t a) :: Bool where ...
- data LookupSym0 (a1 :: TyFun a ([(a, b)] ~> Maybe b))
- data LookupSym1 (a6989586621679814744 :: a) (b1 :: TyFun [(a, b)] (Maybe b))
- type family LookupSym2 (a6989586621679814744 :: a) (a6989586621679814745 :: [(a, b)]) :: Maybe b where ...
- data FindSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Maybe a))
- data FindSym1 (a6989586621680390168 :: a ~> Bool) (b :: TyFun (t a) (Maybe a))
- type family FindSym2 (a6989586621680390168 :: a ~> Bool) (a6989586621680390169 :: t a) :: Maybe a where ...
- data FilterSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data FilterSym1 (a6989586621679815053 :: a ~> Bool) (b :: TyFun [a] [a])
- type family FilterSym2 (a6989586621679815053 :: a ~> Bool) (a6989586621679815054 :: [a]) :: [a] where ...
- data PartitionSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data PartitionSym1 (a6989586621679814737 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family PartitionSym2 (a6989586621679814737 :: a ~> Bool) (a6989586621679814738 :: [a]) :: ([a], [a]) where ...
- data (!!@#@$) (a1 :: TyFun [a] (Natural ~> a))
- data (a6989586621679814661 :: [a]) !!@#@$$ (b :: TyFun Natural a)
- type family (a6989586621679814661 :: [a]) !!@#@$$$ (a6989586621679814662 :: Natural) :: a where ...
- data ElemIndexSym0 (a1 :: TyFun a ([a] ~> Maybe Natural))
- data ElemIndexSym1 (a6989586621679815037 :: a) (b :: TyFun [a] (Maybe Natural))
- type family ElemIndexSym2 (a6989586621679815037 :: a) (a6989586621679815038 :: [a]) :: Maybe Natural where ...
- data ElemIndicesSym0 (a1 :: TyFun a ([a] ~> [Natural]))
- data ElemIndicesSym1 (a6989586621679815028 :: a) (b :: TyFun [a] [Natural])
- type family ElemIndicesSym2 (a6989586621679815028 :: a) (a6989586621679815029 :: [a]) :: [Natural] where ...
- data FindIndexSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural))
- data FindIndexSym1 (a6989586621679815019 :: a ~> Bool) (b :: TyFun [a] (Maybe Natural))
- type family FindIndexSym2 (a6989586621679815019 :: a ~> Bool) (a6989586621679815020 :: [a]) :: Maybe Natural where ...
- data FindIndicesSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [Natural]))
- data FindIndicesSym1 (a6989586621679814996 :: a ~> Bool) (b :: TyFun [a] [Natural])
- type family FindIndicesSym2 (a6989586621679814996 :: a ~> Bool) (a6989586621679814997 :: [a]) :: [Natural] where ...
- data ZipSym0 (a1 :: TyFun [a] ([b] ~> [(a, b)]))
- data ZipSym1 (a6989586621679815371 :: [a]) (b1 :: TyFun [b] [(a, b)])
- type family ZipSym2 (a6989586621679815371 :: [a]) (a6989586621679815372 :: [b]) :: [(a, b)] where ...
- data Zip3Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])))
- data Zip3Sym1 (a6989586621679815359 :: [a]) (b1 :: TyFun [b] ([c] ~> [(a, b, c)]))
- data Zip3Sym2 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (c1 :: TyFun [c] [(a, b, c)])
- type family Zip3Sym3 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (a6989586621679815361 :: [c]) :: [(a, b, c)] where ...
- data Zip4Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))))
- data Zip4Sym1 (a6989586621679966021 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])))
- data Zip4Sym2 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (c1 :: TyFun [c] ([d] ~> [(a, b, c, d)]))
- data Zip4Sym3 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (a6989586621679966023 :: [c]) (d1 :: TyFun [d] [(a, b, c, d)])
- type family Zip4Sym4 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (a6989586621679966023 :: [c]) (a6989586621679966024 :: [d]) :: [(a, b, c, d)] where ...
- data Zip5Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))))
- data Zip5Sym1 (a6989586621679965998 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))))
- data Zip5Sym2 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])))
- data Zip5Sym3 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (d1 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]))
- data Zip5Sym4 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (a6989586621679966001 :: [d]) (e1 :: TyFun [e] [(a, b, c, d, e)])
- type family Zip5Sym5 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (a6989586621679966001 :: [d]) (a6989586621679966002 :: [e]) :: [(a, b, c, d, e)] where ...
- data Zip6Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))))
- data Zip6Sym1 (a6989586621679965970 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))))
- data Zip6Sym2 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))
- data Zip6Sym3 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))
- data Zip6Sym4 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (e1 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]))
- data Zip6Sym5 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (a6989586621679965974 :: [e]) (f1 :: TyFun [f] [(a, b, c, d, e, f)])
- type family Zip6Sym6 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (a6989586621679965974 :: [e]) (a6989586621679965975 :: [f]) :: [(a, b, c, d, e, f)] where ...
- data Zip7Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))))
- data Zip7Sym1 (a6989586621679965937 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))))
- data Zip7Sym2 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))
- data Zip7Sym3 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))
- data Zip7Sym4 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (e1 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))
- data Zip7Sym5 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (f1 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]))
- data Zip7Sym6 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (a6989586621679965942 :: [f]) (g1 :: TyFun [g] [(a, b, c, d, e, f, g)])
- type family Zip7Sym7 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (a6989586621679965942 :: [f]) (a6989586621679965943 :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])))
- data ZipWithSym1 (a6989586621679815347 :: a ~> (b ~> c)) (b1 :: TyFun [a] ([b] ~> [c]))
- data ZipWithSym2 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (c1 :: TyFun [b] [c])
- type family ZipWithSym3 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (a6989586621679815349 :: [b]) :: [c] where ...
- data ZipWith3Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))))
- data ZipWith3Sym1 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (b1 :: TyFun [a] ([b] ~> ([c] ~> [d])))
- data ZipWith3Sym2 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (c1 :: TyFun [b] ([c] ~> [d]))
- data ZipWith3Sym3 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [b]) (d1 :: TyFun [c] [d])
- type family ZipWith3Sym4 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [b]) (a6989586621679815335 :: [c]) :: [d] where ...
- data ZipWith4Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))))
- data ZipWith4Sym1 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))))
- data ZipWith4Sym2 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> [e])))
- data ZipWith4Sym3 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (d1 :: TyFun [c] ([d] ~> [e]))
- data ZipWith4Sym4 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (a6989586621679965904 :: [c]) (e1 :: TyFun [d] [e])
- type family ZipWith4Sym5 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (a6989586621679965904 :: [c]) (a6989586621679965905 :: [d]) :: [e] where ...
- data ZipWith5Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))))
- data ZipWith5Sym1 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))))
- data ZipWith5Sym2 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))))
- data ZipWith5Sym3 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> [f])))
- data ZipWith5Sym4 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (e1 :: TyFun [d] ([e] ~> [f]))
- data ZipWith5Sym5 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (a6989586621679965882 :: [d]) (f1 :: TyFun [e] [f])
- type family ZipWith5Sym6 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (a6989586621679965882 :: [d]) (a6989586621679965883 :: [e]) :: [f] where ...
- data ZipWith6Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))))
- data ZipWith6Sym1 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))))
- data ZipWith6Sym2 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))
- data ZipWith6Sym3 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))))
- data ZipWith6Sym4 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> [g])))
- data ZipWith6Sym5 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (f1 :: TyFun [e] ([f] ~> [g]))
- data ZipWith6Sym6 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (a6989586621679965856 :: [e]) (g1 :: TyFun [f] [g])
- type family ZipWith6Sym7 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (a6989586621679965856 :: [e]) (a6989586621679965857 :: [f]) :: [g] where ...
- data ZipWith7Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))))
- data ZipWith7Sym1 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))))
- data ZipWith7Sym2 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))
- data ZipWith7Sym3 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))
- data ZipWith7Sym4 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))))
- data ZipWith7Sym5 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (f1 :: TyFun [e] ([f] ~> ([g] ~> [h])))
- data ZipWith7Sym6 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (g1 :: TyFun [f] ([g] ~> [h]))
- data ZipWith7Sym7 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (a6989586621679965826 :: [f]) (h1 :: TyFun [g] [h])
- type family ZipWith7Sym8 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (a6989586621679965826 :: [f]) (a6989586621679965827 :: [g]) :: [h] where ...
- data UnzipSym0 (a1 :: TyFun [(a, b)] ([a], [b]))
- type family UnzipSym1 (a6989586621679815313 :: [(a, b)]) :: ([a], [b]) where ...
- data Unzip3Sym0 (a1 :: TyFun [(a, b, c)] ([a], [b], [c]))
- type family Unzip3Sym1 (a6989586621679815295 :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- data Unzip4Sym0 (a1 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]))
- type family Unzip4Sym1 (a6989586621679815275 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ...
- data Unzip5Sym0 (a1 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]))
- type family Unzip5Sym1 (a6989586621679815253 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ...
- data Unzip6Sym0 (a1 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]))
- type family Unzip6Sym1 (a6989586621679815229 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ...
- data Unzip7Sym0 (a1 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]))
- type family Unzip7Sym1 (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- data UnlinesSym0 (a :: TyFun [Symbol] Symbol)
- type family UnlinesSym1 (a6989586621679815198 :: [Symbol]) :: Symbol where ...
- data UnwordsSym0 (a :: TyFun [Symbol] Symbol)
- type family UnwordsSym1 (a6989586621679815188 :: [Symbol]) :: Symbol where ...
- data NubSym0 (a1 :: TyFun [a] [a])
- type family NubSym1 (a6989586621679814644 :: [a]) :: [a] where ...
- data DeleteSym0 (a1 :: TyFun a ([a] ~> [a]))
- data DeleteSym1 (a6989586621679815182 :: a) (b :: TyFun [a] [a])
- type family DeleteSym2 (a6989586621679815182 :: a) (a6989586621679815183 :: [a]) :: [a] where ...
- data (\\@#@$) (a1 :: TyFun [a] ([a] ~> [a]))
- data (a6989586621679815171 :: [a]) \\@#@$$ (b :: TyFun [a] [a])
- type family (a6989586621679815171 :: [a]) \\@#@$$$ (a6989586621679815172 :: [a]) :: [a] where ...
- data UnionSym0 (a1 :: TyFun [a] ([a] ~> [a]))
- data UnionSym1 (a6989586621679814598 :: [a]) (b :: TyFun [a] [a])
- type family UnionSym2 (a6989586621679814598 :: [a]) (a6989586621679814599 :: [a]) :: [a] where ...
- data IntersectSym0 (a1 :: TyFun [a] ([a] ~> [a]))
- data IntersectSym1 (a6989586621679814989 :: [a]) (b :: TyFun [a] [a])
- type family IntersectSym2 (a6989586621679814989 :: [a]) (a6989586621679814990 :: [a]) :: [a] where ...
- data InsertSym0 (a1 :: TyFun a ([a] ~> [a]))
- data InsertSym1 (a6989586621679814791 :: a) (b :: TyFun [a] [a])
- type family InsertSym2 (a6989586621679814791 :: a) (a6989586621679814792 :: [a]) :: [a] where ...
- data SortSym0 (a1 :: TyFun [a] [a])
- type family SortSym1 (a6989586621679814786 :: [a]) :: [a] where ...
- data NubBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]))
- data NubBySym1 (a6989586621679814626 :: a ~> (a ~> Bool)) (b :: TyFun [a] [a])
- type family NubBySym2 (a6989586621679814626 :: a ~> (a ~> Bool)) (a6989586621679814627 :: [a]) :: [a] where ...
- data DeleteBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])))
- data DeleteBySym1 (a6989586621679815152 :: a ~> (a ~> Bool)) (b :: TyFun a ([a] ~> [a]))
- data DeleteBySym2 (a6989586621679815152 :: a ~> (a ~> Bool)) (a6989586621679815153 :: a) (c :: TyFun [a] [a])
- type family DeleteBySym3 (a6989586621679815152 :: a ~> (a ~> Bool)) (a6989586621679815153 :: a) (a6989586621679815154 :: [a]) :: [a] where ...
- data DeleteFirstsBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data DeleteFirstsBySym1 (a6989586621679815142 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data DeleteFirstsBySym2 (a6989586621679815142 :: a ~> (a ~> Bool)) (a6989586621679815143 :: [a]) (c :: TyFun [a] [a])
- type family DeleteFirstsBySym3 (a6989586621679815142 :: a ~> (a ~> Bool)) (a6989586621679815143 :: [a]) (a6989586621679815144 :: [a]) :: [a] where ...
- data UnionBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data UnionBySym1 (a6989586621679814606 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data UnionBySym2 (a6989586621679814606 :: a ~> (a ~> Bool)) (a6989586621679814607 :: [a]) (c :: TyFun [a] [a])
- type family UnionBySym3 (a6989586621679814606 :: a ~> (a ~> Bool)) (a6989586621679814607 :: [a]) (a6989586621679814608 :: [a]) :: [a] where ...
- data IntersectBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data IntersectBySym1 (a6989586621679814967 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data IntersectBySym2 (a6989586621679814967 :: a ~> (a ~> Bool)) (a6989586621679814968 :: [a]) (c :: TyFun [a] [a])
- type family IntersectBySym3 (a6989586621679814967 :: a ~> (a ~> Bool)) (a6989586621679814968 :: [a]) (a6989586621679814969 :: [a]) :: [a] where ...
- data GroupBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]))
- data GroupBySym1 (a6989586621679814759 :: a ~> (a ~> Bool)) (b :: TyFun [a] [[a]])
- type family GroupBySym2 (a6989586621679814759 :: a ~> (a ~> Bool)) (a6989586621679814760 :: [a]) :: [[a]] where ...
- data SortBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]))
- data SortBySym1 (a6989586621679815130 :: a ~> (a ~> Ordering)) (b :: TyFun [a] [a])
- type family SortBySym2 (a6989586621679815130 :: a ~> (a ~> Ordering)) (a6989586621679815131 :: [a]) :: [a] where ...
- data InsertBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])))
- data InsertBySym1 (a6989586621679815110 :: a ~> (a ~> Ordering)) (b :: TyFun a ([a] ~> [a]))
- data InsertBySym2 (a6989586621679815110 :: a ~> (a ~> Ordering)) (a6989586621679815111 :: a) (c :: TyFun [a] [a])
- type family InsertBySym3 (a6989586621679815110 :: a ~> (a ~> Ordering)) (a6989586621679815111 :: a) (a6989586621679815112 :: [a]) :: [a] where ...
- data MaximumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a))
- data MaximumBySym1 (a6989586621680390215 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a)
- type family MaximumBySym2 (a6989586621680390215 :: a ~> (a ~> Ordering)) (a6989586621680390216 :: t a) :: a where ...
- data MinimumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a))
- data MinimumBySym1 (a6989586621680390195 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a)
- type family MinimumBySym2 (a6989586621680390195 :: a ~> (a ~> Ordering)) (a6989586621680390196 :: t a) :: a where ...
- data GenericLengthSym0 (a1 :: TyFun [a] i)
- type family GenericLengthSym1 (a6989586621679814589 :: [a]) :: i where ...
The singleton for lists
type family Sing :: k -> Type #
Instances
data SList (a1 :: [a]) where Source #
Constructors
| SNil :: forall a. SList ('[] :: [a]) | |
| SCons :: forall a (n1 :: a) (n2 :: [a]). Sing n1 -> Sing n2 -> SList (n1 ': n2) infixr 5 |
Instances
| (SDecide a, SDecide [a]) => TestCoercion (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| (SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| (ShowSing a, ShowSing [a]) => Show (SList z) Source # | |
| Eq (SList z) Source # | |
Basic functions
(%++) :: forall a (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) infixr 5 Source #
type family Null (arg :: t a) :: Bool Source #
Instances
sNull :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Apply (NullSym0 :: TyFun (t a) Bool -> Type) t1) Source #
type family Length (arg :: t a) :: Natural Source #
Instances
sLength :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (t a) Natural -> Type) t1) Source #
List transformations
sMap :: forall a b (t1 :: a ~> b) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) t1) t2) Source #
sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply (ReverseSym0 :: TyFun [a] [a] -> Type) t) Source #
type family Intersperse (a1 :: a) (a2 :: [a]) :: [a] where ... Source #
sIntersperse :: forall a (t1 :: a) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2) Source #
type family Intercalate (a1 :: [a]) (a2 :: [[a]]) :: [a] where ... Source #
Equations
| Intercalate (xs :: [a]) (xss :: [[a]]) = Apply (ConcatSym0 :: TyFun [[a]] [a] -> Type) (Apply (Apply (IntersperseSym0 :: TyFun [a] ([[a]] ~> [[a]]) -> Type) xs) xss) |
sIntercalate :: forall a (t1 :: [a]) (t2 :: [[a]]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) t1) t2) Source #
type family Transpose (a1 :: [[a]]) :: [[a]] where ... Source #
Equations
| Transpose ('[] :: [[a]]) = NilSym0 :: [[a]] | |
| Transpose (('[] :: [a]) ': xss :: [[a]]) = Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) xss | |
| Transpose ((x ': xs) ': xss :: [[a]]) = Apply (Apply ((:@#@$) :: TyFun [a] ([[a]] ~> [[a]]) -> Type) (Apply (Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) x) (Apply (Apply (MapSym0 :: TyFun ([a] ~> a) ([[a]] ~> [a]) -> Type) (HeadSym0 :: TyFun [a] a -> Type)) xss))) (Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (Apply (Apply ((:@#@$) :: TyFun [a] ([[a]] ~> [[a]]) -> Type) xs) (Apply (Apply (MapSym0 :: TyFun ([a] ~> [a]) ([[a]] ~> [[a]]) -> Type) (TailSym0 :: TyFun [a] [a] -> Type)) xss))) |
sTranspose :: forall a (t :: [[a]]). Sing t -> Sing (Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) t) Source #
type family Subsequences (a1 :: [a]) :: [[a]] where ... Source #
sSubsequences :: forall a (t :: [a]). Sing t -> Sing (Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) t) Source #
type family Permutations (a1 :: [a]) :: [[a]] where ... Source #
sPermutations :: forall a (t :: [a]). Sing t -> Sing (Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) t) Source #
Reducing lists (folds)
type family Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) :: b Source #
Instances
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg :: b ~> (a1 ~> b)) (arg1 :: b) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #
type family Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) :: b Source #
Instances
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg :: b ~> (a1 ~> b)) (arg1 :: b) (arg2 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #
type family Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #
Instances
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg :: a1 ~> (a1 ~> a1)) (arg1 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #
sFoldl1' :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) t1) t2) Source #
type family Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: t a) :: b Source #
Instances
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Max a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Min a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: [a1]) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr (a3 :: a1 ~> (k2 ~> k2)) (a4 :: k2) (a5 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Const m a1) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #
type family Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #
Instances
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg :: a1 ~> (a1 ~> a1)) (arg1 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) Source # | |
Defined in Data.Foldable.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). SFoldable t => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #
Special folds
sConcat :: forall (t1 :: Type -> Type) a (t2 :: t1 [a]). SFoldable t1 => Sing t2 -> Sing (Apply (ConcatSym0 :: TyFun (t1 [a]) [a] -> Type) t2) Source #
type family ConcatMap (a1 :: a ~> [b]) (a2 :: t a) :: [b] where ... Source #
Equations
| ConcatMap (f :: a1 ~> [a2]) (xs :: t a1) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a1 ~> ([a2] ~> [a2])) ([a2] ~> (t a1 ~> [a2])) -> Type) (Apply (Apply (Lambda_6989586621680390267Sym0 :: TyFun (a1 ~> [a2]) (TyFun (t a1) (TyFun a1 (TyFun [a2] [a2] -> Type) -> Type) -> Type) -> Type) f) xs)) (NilSym0 :: [a2])) xs |
sConcatMap :: forall a b (t1 :: Type -> Type) (t2 :: a ~> [b]) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t1 a ~> [b]) -> Type) t2) t3) Source #
sAnd :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (AndSym0 :: TyFun (t1 Bool) Bool -> Type) t2) Source #
sOr :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (OrSym0 :: TyFun (t1 Bool) Bool -> Type) t2) Source #
type family Any (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #
Equations
| Any (p :: a ~> Bool) (a_6989586621680390239 :: t a) = Apply (Apply (Apply ((.@#@$) :: TyFun (Any ~> Bool) ((t a ~> Any) ~> (t a ~> Bool)) -> Type) GetAnySym0) (Apply (FoldMapSym0 :: TyFun (a ~> Any) (t a ~> Any) -> Type) (Apply (Apply ((.@#@$) :: TyFun (Bool ~> Any) ((a ~> Bool) ~> (a ~> Any)) -> Type) Any_Sym0) p))) a_6989586621680390239 |
sAny :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AnySym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) t2) t3) Source #
type family All (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #
Equations
| All (p :: a ~> Bool) (a_6989586621680390230 :: t a) = Apply (Apply (Apply ((.@#@$) :: TyFun (All ~> Bool) ((t a ~> All) ~> (t a ~> Bool)) -> Type) GetAllSym0) (Apply (FoldMapSym0 :: TyFun (a ~> All) (t a ~> All) -> Type) (Apply (Apply ((.@#@$) :: TyFun (Bool ~> All) ((a ~> Bool) ~> (a ~> All)) -> Type) All_Sym0) p))) a_6989586621680390230 |
sAll :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AllSym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) t2) t3) Source #
type family Sum (arg :: t a) :: a Source #
Instances
sSum :: forall a (t1 :: t a). (SFoldable t, SNum a) => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (t a) a -> Type) t1) Source #
type family Product (arg :: t a) :: a Source #
Instances
sProduct :: forall a (t1 :: t a). (SFoldable t, SNum a) => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (t a) a -> Type) t1) Source #
type family Maximum (arg :: t a) :: a Source #
Instances
sMaximum :: forall a (t1 :: t a). (SFoldable t, SOrd a) => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (t a) a -> Type) t1) Source #
type family Minimum (arg :: t a) :: a Source #
Instances
sMinimum :: forall a (t1 :: t a). (SFoldable t, SOrd a) => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (t a) a -> Type) t1) Source #
Building lists
Scans
sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) t1) t2) t3) Source #
sScanl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) t1) t2) Source #
type family Scanr (a1 :: a ~> (b ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ... Source #
Equations
| Scanr (_1 :: a ~> (k1 ~> k1)) (q0 :: k1) ('[] :: [a]) = Apply (Apply ((:@#@$) :: TyFun k1 ([k1] ~> [k1]) -> Type) q0) (NilSym0 :: [k1]) | |
| Scanr (f :: k ~> (k1 ~> k1)) (q0 :: k1) (x ': xs :: [k]) = Case_6989586621679815574 f q0 x xs (Let6989586621679815572Scrutinee_6989586621679811480Sym4 f q0 x xs) |
sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) t1) t2) t3) Source #
type family Scanr1 (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: [a] where ... Source #
Equations
| Scanr1 (_1 :: a ~> (a ~> a)) ('[] :: [a]) = NilSym0 :: [a] | |
| Scanr1 (_1 :: k1 ~> (k1 ~> k1)) ('[x] :: [k1]) = Apply (Apply ((:@#@$) :: TyFun k1 ([k1] ~> [k1]) -> Type) x) (NilSym0 :: [k1]) | |
| Scanr1 (f :: k ~> (k ~> k)) (x ': (wild_6989586621679811492 ': wild_6989586621679811494) :: [k]) = Case_6989586621679815555 f x wild_6989586621679811492 wild_6989586621679811494 (Let6989586621679815553Scrutinee_6989586621679811486Sym4 f x wild_6989586621679811492 wild_6989586621679811494) |
sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) t1) t2) Source #
Accumulating maps
type family MapAccumL (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumL (f :: a ~> (b ~> (a, c))) (s :: a) (t2 :: t1 b) = Apply (Apply (RunStateLSym0 :: TyFun (StateL a (t1 c)) (a ~> (a, t1 c)) -> Type) (Apply (Apply (TraverseSym0 :: TyFun (b ~> StateL a c) (t1 b ~> StateL a (t1 c)) -> Type) (Apply (Apply ((.@#@$) :: TyFun ((a ~> (a, c)) ~> StateL a c) ((b ~> (a ~> (a, c))) ~> (b ~> StateL a c)) -> Type) (StateLSym0 :: TyFun (a ~> (a, c)) (StateL a c) -> Type)) (Apply (FlipSym0 :: TyFun (a ~> (b ~> (a, c))) (b ~> (a ~> (a, c))) -> Type) f))) t2)) s |
sMapAccumL :: forall (t1 :: Type -> Type) a b c (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t1 b ~> (a, t1 c))) -> Type) t2) t3) t4) Source #
type family MapAccumR (a1 :: a ~> (b ~> (a, c))) (a2 :: a) (a3 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumR (f :: k1 ~> (a ~> (k1, b))) (s :: k1) (t2 :: t1 a) = Apply (Apply (RunStateRSym0 :: TyFun (StateR k1 (t1 b)) (k1 ~> (k1, t1 b)) -> Type) (Apply (Apply (TraverseSym0 :: TyFun (a ~> StateR k1 b) (t1 a ~> StateR k1 (t1 b)) -> Type) (Apply (Apply ((.@#@$) :: TyFun ((k1 ~> (k1, b)) ~> StateR k1 b) ((a ~> (k1 ~> (k1, b))) ~> (a ~> StateR k1 b)) -> Type) (StateRSym0 :: TyFun (k1 ~> (k1, b)) (StateR k1 b) -> Type)) (Apply (FlipSym0 :: TyFun (k1 ~> (a ~> (k1, b))) (a ~> (k1 ~> (k1, b))) -> Type) f))) t2)) s |
sMapAccumR :: forall a b c (t1 :: Type -> Type) (t2 :: a ~> (b ~> (a, c))) (t3 :: a) (t4 :: t1 b). STraversable t1 => Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t1 b ~> (a, t1 c))) -> Type) t2) t3) t4) Source #
Cyclical lists
type family Replicate (a1 :: Natural) (a2 :: a) :: [a] where ... Source #
Equations
| Replicate n (x :: k) = Case_6989586621679814687 n x (Let6989586621679814685Scrutinee_6989586621679811588Sym2 n x) |
sReplicate :: forall a (t1 :: Natural) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) t1) t2) Source #
Unfolding
sUnfoldr :: forall b a (t1 :: b ~> Maybe (a, b)) (t2 :: b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) t1) t2) Source #
Sublists
Extracting sublists
sTake :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) t1) t2) Source #
sDrop :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) t1) t2) Source #
sSplitAt :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) t1) t2) Source #
sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2) Source #
sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2) Source #
type family DropWhileEnd (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ... Source #
Equations
| DropWhileEnd (p :: a ~> Bool) (a_6989586621679814916 :: [a]) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> ([a] ~> [a])) ([a] ~> ([a] ~> [a])) -> Type) (Apply (Apply (Lambda_6989586621679814925Sym0 :: TyFun (a ~> Bool) (TyFun [a] (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) p) a_6989586621679814916)) (NilSym0 :: [a])) a_6989586621679814916 |
sDropWhileEnd :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2) Source #
type family Span (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ... Source #
Equations
| Span (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679814886XsSym0 :: [a])) (Let6989586621679814886XsSym0 :: [a]) | |
| Span (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679814895 p x xs' (Let6989586621679814893Scrutinee_6989586621679811568Sym3 p x xs') |
sSpan :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2) Source #
type family Break (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ... Source #
Equations
| Break (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679814851XsSym0 :: [a])) (Let6989586621679814851XsSym0 :: [a]) | |
| Break (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679814860 p x xs' (Let6989586621679814858Scrutinee_6989586621679811570Sym3 p x xs') |
sBreak :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2) Source #
type family StripPrefix (a1 :: [a]) (a2 :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefix ('[] :: [a]) (ys :: [a]) = Apply (JustSym0 :: TyFun [a] (Maybe [a]) -> Type) ys | |
| StripPrefix (arg_6989586621679964723 :: [k]) (arg_6989586621679964725 :: [k]) = Case_6989586621679966037 arg_6989586621679964723 arg_6989586621679964725 (Apply (Apply (Tuple2Sym0 :: TyFun [k] ([k] ~> ([k], [k])) -> Type) arg_6989586621679964723) arg_6989586621679964725) |
sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) t) Source #
sInits :: forall a (t :: [a]). Sing t -> Sing (Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) t) Source #
sTails :: forall a (t :: [a]). Sing t -> Sing (Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) t) Source #
Predicates
type family IsPrefixOf (a1 :: [a]) (a2 :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOf ('[] :: [a]) ('[] :: [a]) = TrueSym0 | |
| IsPrefixOf ('[] :: [a]) (_1 ': _2 :: [a]) = TrueSym0 | |
| IsPrefixOf (_1 ': _2 :: [a]) ('[] :: [a]) = FalseSym0 | |
| IsPrefixOf (x ': xs :: [a]) (y ': ys :: [a]) = Apply (Apply (&&@#@$) (Apply (Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) x) y)) (Apply (Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) xs) ys) |
sIsPrefixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #
type family IsSuffixOf (a1 :: [a]) (a2 :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOf (x :: [a]) (y :: [a]) = Apply (Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (Apply (ReverseSym0 :: TyFun [a] [a] -> Type) x)) (Apply (ReverseSym0 :: TyFun [a] [a] -> Type) y) |
sIsSuffixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #
sIsInfixOf :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #
Searching lists
Searching by equality
type family Elem (arg :: a) (arg1 :: t a) :: Bool Source #
Instances
| type Elem (arg1 :: a) (arg2 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Last a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg :: a) (arg1 :: First a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg :: a) (arg1 :: Last a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg :: a) (arg1 :: Max a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg :: a) (arg1 :: Min a) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a) (arg2 :: NonEmpty a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg1 :: a) (arg2 :: Maybe a) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Identity k1) Source # | |
Defined in Data.Functor.Identity.Singletons | |
| type Elem (a1 :: k1) (a2 :: Dual k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Product k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: Sum k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (a1 :: k1) (a2 :: [k1]) Source # | |
Defined in Data.Foldable.Singletons type Elem (a1 :: k1) (a2 :: [k1]) | |
| type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg :: a1) (arg1 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
| type Elem (arg1 :: a1) (arg2 :: (a2, a1)) Source # | |
Defined in Data.Foldable.Singletons type Elem (arg1 :: a1) (arg2 :: (a2, a1)) | |
| type Elem (a1 :: k1) (a2 :: Proxy k1) Source # | |
Defined in Data.Foldable.Singletons | |
| type Elem (arg :: a) (arg1 :: Const m a) Source # | |
Defined in Data.Functor.Const.Singletons | |
| type Elem (arg :: a) (arg1 :: Product f g a) Source # | |
Defined in Data.Functor.Product.Singletons | |
| type Elem (arg :: a) (arg1 :: Sum f g a) Source # | |
Defined in Data.Functor.Sum.Singletons | |
| type Elem (arg :: a) (arg1 :: Compose f g a) Source # | |
Defined in Data.Functor.Compose.Singletons | |
sElem :: forall a (t1 :: a) (t2 :: t a). (SFoldable t, SEq a) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2) Source #
sNotElem :: forall a (t1 :: Type -> Type) (t2 :: a) (t3 :: t1 a). (SFoldable t1, SEq a) => Sing t2 -> Sing t3 -> Sing (Apply (Apply (NotElemSym0 :: TyFun a (t1 a ~> Bool) -> Type) t2) t3) Source #
type family Lookup (a1 :: a) (a2 :: [(a, b)]) :: Maybe b where ... Source #
Equations
| Lookup (_key :: a) ('[] :: [(a, b)]) = NothingSym0 :: Maybe b | |
| Lookup (key :: k1) ('(x, y) ': xys :: [(k1, k)]) = Case_6989586621679814753 key x y xys (Let6989586621679814751Scrutinee_6989586621679811584Sym4 key x y xys) |
sLookup :: forall a b (t1 :: a) (t2 :: [(a, b)]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) t1) t2) Source #
Searching with a predicate
type family Find (a1 :: a ~> Bool) (a2 :: t a) :: Maybe a where ... Source #
Equations
| Find (p :: a ~> Bool) (a_6989586621680390163 :: t a) = Apply (Apply (Apply ((.@#@$) :: TyFun (First a ~> Maybe a) ((t a ~> First a) ~> (t a ~> Maybe a)) -> Type) (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type)) (Apply (FoldMapSym0 :: TyFun (a ~> First a) (t a ~> First a) -> Type) (Apply (Apply (Lambda_6989586621680390172Sym0 :: TyFun (a ~> Bool) (TyFun (t a) (TyFun a (First a) -> Type) -> Type) -> Type) p) a_6989586621680390163))) a_6989586621680390163 |
sFind :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (FindSym0 :: TyFun (a ~> Bool) (t1 a ~> Maybe a) -> Type) t2) t3) Source #
sFilter :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) t1) t2) Source #
type family Partition (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ... Source #
Equations
| Partition (p :: a ~> Bool) (xs :: [a]) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (([a], [a]) ~> ([a], [a]))) (([a], [a]) ~> ([a] ~> ([a], [a]))) -> Type) (Apply (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) p)) (Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (NilSym0 :: [a])) (NilSym0 :: [a]))) xs |
sPartition :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) t1) t2) Source #
Indexing lists
(%!!) :: forall a (t1 :: [a]) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) t1) t2) infixl 9 Source #
sElemIndex :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) t1) t2) Source #
type family ElemIndices (a1 :: a) (a2 :: [a]) :: [Natural] where ... Source #
sElemIndices :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) t1) t2) Source #
type family FindIndex (a1 :: a ~> Bool) (a2 :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndex (p :: a ~> Bool) (a_6989586621679815014 :: [a]) = Apply (Apply (Apply ((.@#@$) :: TyFun ([Natural] ~> Maybe Natural) (([a] ~> [Natural]) ~> ([a] ~> Maybe Natural)) -> Type) (ListToMaybeSym0 :: TyFun [Natural] (Maybe Natural) -> Type)) (Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) p)) a_6989586621679815014 |
sFindIndex :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) t1) t2) Source #
type family FindIndices (a1 :: a ~> Bool) (a2 :: [a]) :: [Natural] where ... Source #
Equations
| FindIndices (p :: a ~> Bool) (xs :: [a]) = Apply (Apply (MapSym0 :: TyFun ((a, Natural) ~> Natural) ([(a, Natural)] ~> [Natural]) -> Type) (SndSym0 :: TyFun (a, Natural) Natural -> Type)) (Apply (Apply (FilterSym0 :: TyFun ((a, Natural) ~> Bool) ([(a, Natural)] ~> [(a, Natural)]) -> Type) (Apply (Apply (Lambda_6989586621679815006Sym0 :: TyFun (a ~> Bool) (TyFun [a] (TyFun (a, Natural) Bool -> Type) -> Type) -> Type) p) xs)) (Apply (Apply (ZipSym0 :: TyFun [a] ([Natural] ~> [(a, Natural)]) -> Type) xs) (Apply (Apply (Let6989586621679815000BuildListSym2 p xs :: TyFun Natural ([a] ~> [Natural]) -> Type) (FromInteger 0 :: Natural)) xs))) |
sFindIndices :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) t1) t2) Source #
Zipping and unzipping lists
type family Zip (a1 :: [a]) (a2 :: [b]) :: [(a, b)] where ... Source #
Equations
| Zip (x ': xs :: [a]) (y ': ys :: [b]) = Apply (Apply ((:@#@$) :: TyFun (a, b) ([(a, b)] ~> [(a, b)]) -> Type) (Apply (Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) x) y)) (Apply (Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) xs) ys) | |
| Zip ('[] :: [a]) ('[] :: [b]) = NilSym0 :: [(a, b)] | |
| Zip (_1 ': _2 :: [a]) ('[] :: [b]) = NilSym0 :: [(a, b)] | |
| Zip ('[] :: [a]) (_1 ': _2 :: [b]) = NilSym0 :: [(a, b)] |
sZip :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) t1) t2) Source #
type family Zip3 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) :: [(a, b, c)] where ... Source #
Equations
| Zip3 (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) = Apply (Apply ((:@#@$) :: TyFun (a1, b1, c1) ([(a1, b1, c1)] ~> [(a1, b1, c1)]) -> Type) (Apply (Apply (Apply (Tuple3Sym0 :: TyFun a1 (b1 ~> (c1 ~> (a1, b1, c1))) -> Type) a2) b2) c2)) (Apply (Apply (Apply (Zip3Sym0 :: TyFun [a1] ([b1] ~> ([c1] ~> [(a1, b1, c1)])) -> Type) as) bs) cs) | |
| Zip3 ('[] :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 ('[] :: [a]) ('[] :: [b]) (_1 ': _2 :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 ('[] :: [a]) (_1 ': _2 :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 ('[] :: [a]) (_1 ': _2 :: [b]) (_3 ': _4 :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 (_1 ': _2 :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 (_1 ': _2 :: [a]) ('[] :: [b]) (_3 ': _4 :: [c]) = NilSym0 :: [(a, b, c)] | |
| Zip3 (_1 ': _2 :: [a]) (_3 ': _4 :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] |
sZip3 :: forall a b c (t1 :: [a]) (t2 :: [b]) (t3 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) t1) t2) t3) Source #
type family Zip4 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) :: [(a, b, c, d)] where ... Source #
Equations
| Zip4 (a_6989586621679966008 :: [a]) (a_6989586621679966010 :: [b]) (a_6989586621679966012 :: [c]) (a_6989586621679966014 :: [d]) = Apply (Apply (Apply (Apply (Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (a, b, c, d))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)])))) -> Type) (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type)) a_6989586621679966008) a_6989586621679966010) a_6989586621679966012) a_6989586621679966014 |
type family Zip5 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) :: [(a, b, c, d, e)] where ... Source #
Equations
| Zip5 (a_6989586621679965982 :: [a]) (a_6989586621679965984 :: [b]) (a_6989586621679965986 :: [c]) (a_6989586621679965988 :: [d]) (a_6989586621679965990 :: [e]) = Apply (Apply (Apply (Apply (Apply (Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))))) -> Type) (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type)) a_6989586621679965982) a_6989586621679965984) a_6989586621679965986) a_6989586621679965988) a_6989586621679965990 |
type family Zip6 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) (a6 :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Equations
| Zip6 (a_6989586621679965951 :: [a]) (a_6989586621679965953 :: [b]) (a_6989586621679965955 :: [c]) (a_6989586621679965957 :: [d]) (a_6989586621679965959 :: [e]) (a_6989586621679965961 :: [f]) = Apply (Apply (Apply (Apply (Apply (Apply (Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))))) -> Type) (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type)) a_6989586621679965951) a_6989586621679965953) a_6989586621679965955) a_6989586621679965957) a_6989586621679965959) a_6989586621679965961 |
type family Zip7 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) (a6 :: [f]) (a7 :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
| Zip7 (a_6989586621679965915 :: [a]) (a_6989586621679965917 :: [b]) (a_6989586621679965919 :: [c]) (a_6989586621679965921 :: [d]) (a_6989586621679965923 :: [e]) (a_6989586621679965925 :: [f]) (a_6989586621679965927 :: [g]) = Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))))) -> Type) (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type)) a_6989586621679965915) a_6989586621679965917) a_6989586621679965919) a_6989586621679965921) a_6989586621679965923) a_6989586621679965925) a_6989586621679965927 |
type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: [a]) (a3 :: [b]) :: [c] where ... Source #
Equations
| ZipWith (f :: a ~> (b ~> c)) (x ': xs :: [a]) (y ': ys :: [b]) = Apply (Apply ((:@#@$) :: TyFun c ([c] ~> [c]) -> Type) (Apply (Apply f x) y)) (Apply (Apply (Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) f) xs) ys) | |
| ZipWith (_1 :: a ~> (b ~> c)) ('[] :: [a]) ('[] :: [b]) = NilSym0 :: [c] | |
| ZipWith (_1 :: a ~> (b ~> c)) (_2 ': _3 :: [a]) ('[] :: [b]) = NilSym0 :: [c] | |
| ZipWith (_1 :: a ~> (b ~> c)) ('[] :: [a]) (_2 ': _3 :: [b]) = NilSym0 :: [c] |
sZipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) t1) t2) t3) Source #
type family ZipWith3 (a1 :: a ~> (b ~> (c ~> d))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) :: [d] where ... Source #
Equations
| ZipWith3 (z :: a1 ~> (b1 ~> (c1 ~> d))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) = Apply (Apply ((:@#@$) :: TyFun d ([d] ~> [d]) -> Type) (Apply (Apply (Apply z a2) b2) c2)) (Apply (Apply (Apply (Apply (ZipWith3Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> d))) ([a1] ~> ([b1] ~> ([c1] ~> [d]))) -> Type) z) as) bs) cs) | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) ('[] :: [b]) (_2 ': _3 :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) (_2 ': _3 :: [b]) ('[] :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) (_2 ': _3 :: [b]) (_4 ': _5 :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) ('[] :: [b]) (_4 ': _5 :: [c]) = NilSym0 :: [d] | |
| ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) (_4 ': _5 :: [b]) ('[] :: [c]) = NilSym0 :: [d] |
sZipWith3 :: forall a b c d (t1 :: a ~> (b ~> (c ~> d))) (t2 :: [a]) (t3 :: [b]) (t4 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing (Apply (Apply (Apply (Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) t1) t2) t3) t4) Source #
type family ZipWith4 (a1 :: a ~> (b ~> (c ~> (d ~> e)))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) :: [e] where ... Source #
Equations
| ZipWith4 (z :: a1 ~> (b1 ~> (c1 ~> (d1 ~> e)))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) (d2 ': ds :: [d1]) = Apply (Apply ((:@#@$) :: TyFun e ([e] ~> [e]) -> Type) (Apply (Apply (Apply (Apply z a2) b2) c2) d2)) (Apply (Apply (Apply (Apply (Apply (ZipWith4Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> (d1 ~> e)))) ([a1] ~> ([b1] ~> ([c1] ~> ([d1] ~> [e])))) -> Type) z) as) bs) cs) ds) | |
| ZipWith4 (_1 :: a ~> (b ~> (c ~> (d ~> e)))) (_2 :: [a]) (_3 :: [b]) (_4 :: [c]) (_5 :: [d]) = NilSym0 :: [e] |
type family ZipWith5 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) :: [f] where ... Source #
Equations
| ZipWith5 (z :: a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> f))))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) (d2 ': ds :: [d1]) (e2 ': es :: [e1]) = Apply (Apply ((:@#@$) :: TyFun f ([f] ~> [f]) -> Type) (Apply (Apply (Apply (Apply (Apply z a2) b2) c2) d2) e2)) (Apply (Apply (Apply (Apply (Apply (Apply (ZipWith5Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> f))))) ([a1] ~> ([b1] ~> ([c1] ~> ([d1] ~> ([e1] ~> [f]))))) -> Type) z) as) bs) cs) ds) es) | |
| ZipWith5 (_1 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (_2 :: [a]) (_3 :: [b]) (_4 :: [c]) (_5 :: [d]) (_6 :: [e]) = NilSym0 :: [f] |
type family ZipWith6 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) (a7 :: [f]) :: [g] where ... Source #
Equations
| ZipWith6 (z :: a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> (f1 ~> g)))))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) (d2 ': ds :: [d1]) (e2 ': es :: [e1]) (f2 ': fs :: [f1]) = Apply (Apply ((:@#@$) :: TyFun g ([g] ~> [g]) -> Type) (Apply (Apply (Apply (Apply (Apply (Apply z a2) b2) c2) d2) e2) f2)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (ZipWith6Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> (f1 ~> g)))))) ([a1] ~> ([b1] ~> ([c1] ~> ([d1] ~> ([e1] ~> ([f1] ~> [g])))))) -> Type) z) as) bs) cs) ds) es) fs) | |
| ZipWith6 (_1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (_2 :: [a]) (_3 :: [b]) (_4 :: [c]) (_5 :: [d]) (_6 :: [e]) (_7 :: [f]) = NilSym0 :: [g] |
type family ZipWith7 (a1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) (a5 :: [d]) (a6 :: [e]) (a7 :: [f]) (a8 :: [g]) :: [h] where ... Source #
Equations
| ZipWith7 (z :: a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> (f1 ~> (g1 ~> h))))))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) (d2 ': ds :: [d1]) (e2 ': es :: [e1]) (f2 ': fs :: [f1]) (g2 ': gs :: [g1]) = Apply (Apply ((:@#@$) :: TyFun h ([h] ~> [h]) -> Type) (Apply (Apply (Apply (Apply (Apply (Apply (Apply z a2) b2) c2) d2) e2) f2) g2)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Apply (ZipWith7Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> (d1 ~> (e1 ~> (f1 ~> (g1 ~> h))))))) ([a1] ~> ([b1] ~> ([c1] ~> ([d1] ~> ([e1] ~> ([f1] ~> ([g1] ~> [h]))))))) -> Type) z) as) bs) cs) ds) es) fs) gs) | |
| ZipWith7 (_1 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (_2 :: [a]) (_3 :: [b]) (_4 :: [c]) (_5 :: [d]) (_6 :: [e]) (_7 :: [f]) (_8 :: [g]) = NilSym0 :: [h] |
type family Unzip (a1 :: [(a, b)]) :: ([a], [b]) where ... Source #
Equations
| Unzip (xs :: [(k2, k3)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3) ~> (([k2], [k3]) ~> ([k2], [k3]))) (([k2], [k3]) ~> ([(k2, k3)] ~> ([k2], [k3]))) -> Type) (Apply (Lambda_6989586621679815315Sym0 :: TyFun [(k2, k3)] (TyFun (k2, k3) (TyFun ([k2], [k3]) ([k2], [k3]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Tuple2Sym0 :: TyFun [k2] ([k3] ~> ([k2], [k3])) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3]))) xs |
sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) t) Source #
type family Unzip3 (a1 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Equations
| Unzip3 (xs :: [(k2, k3, k4)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4) ~> (([k2], [k3], [k4]) ~> ([k2], [k3], [k4]))) (([k2], [k3], [k4]) ~> ([(k2, k3, k4)] ~> ([k2], [k3], [k4]))) -> Type) (Apply (Lambda_6989586621679815297Sym0 :: TyFun [(k2, k3, k4)] (TyFun (k2, k3, k4) (TyFun ([k2], [k3], [k4]) ([k2], [k3], [k4]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Apply (Tuple3Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k2], [k3], [k4]))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4]))) xs |
sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) t) Source #
type family Unzip4 (a1 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #
Equations
| Unzip4 (xs :: [(k2, k3, k4, k5)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4, k5) ~> (([k2], [k3], [k4], [k5]) ~> ([k2], [k3], [k4], [k5]))) (([k2], [k3], [k4], [k5]) ~> ([(k2, k3, k4, k5)] ~> ([k2], [k3], [k4], [k5]))) -> Type) (Apply (Lambda_6989586621679815277Sym0 :: TyFun [(k2, k3, k4, k5)] (TyFun (k2, k3, k4, k5) (TyFun ([k2], [k3], [k4], [k5]) ([k2], [k3], [k4], [k5]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Apply (Apply (Tuple4Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k5] ~> ([k2], [k3], [k4], [k5])))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4])) (NilSym0 :: [k5]))) xs |
sUnzip4 :: forall a b c d (t :: [(a, b, c, d)]). Sing t -> Sing (Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) t) Source #
type family Unzip5 (a1 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #
Equations
| Unzip5 (xs :: [(k2, k3, k4, k5, k6)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4, k5, k6) ~> (([k2], [k3], [k4], [k5], [k6]) ~> ([k2], [k3], [k4], [k5], [k6]))) (([k2], [k3], [k4], [k5], [k6]) ~> ([(k2, k3, k4, k5, k6)] ~> ([k2], [k3], [k4], [k5], [k6]))) -> Type) (Apply (Lambda_6989586621679815255Sym0 :: TyFun [(k2, k3, k4, k5, k6)] (TyFun (k2, k3, k4, k5, k6) (TyFun ([k2], [k3], [k4], [k5], [k6]) ([k2], [k3], [k4], [k5], [k6]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Apply (Apply (Apply (Tuple5Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k5] ~> ([k6] ~> ([k2], [k3], [k4], [k5], [k6]))))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4])) (NilSym0 :: [k5])) (NilSym0 :: [k6]))) xs |
sUnzip5 :: forall a b c d e (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) t) Source #
type family Unzip6 (a1 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #
Equations
| Unzip6 (xs :: [(k2, k3, k4, k5, k6, k7)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4, k5, k6, k7) ~> (([k2], [k3], [k4], [k5], [k6], [k7]) ~> ([k2], [k3], [k4], [k5], [k6], [k7]))) (([k2], [k3], [k4], [k5], [k6], [k7]) ~> ([(k2, k3, k4, k5, k6, k7)] ~> ([k2], [k3], [k4], [k5], [k6], [k7]))) -> Type) (Apply (Lambda_6989586621679815231Sym0 :: TyFun [(k2, k3, k4, k5, k6, k7)] (TyFun (k2, k3, k4, k5, k6, k7) (TyFun ([k2], [k3], [k4], [k5], [k6], [k7]) ([k2], [k3], [k4], [k5], [k6], [k7]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Tuple6Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k5] ~> ([k6] ~> ([k7] ~> ([k2], [k3], [k4], [k5], [k6], [k7])))))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4])) (NilSym0 :: [k5])) (NilSym0 :: [k6])) (NilSym0 :: [k7]))) xs |
sUnzip6 :: forall a b c d e f (t :: [(a, b, c, d, e, f)]). Sing t -> Sing (Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) t) Source #
type family Unzip7 (a1 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Equations
| Unzip7 (xs :: [(k2, k3, k4, k5, k6, k7, k8)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4, k5, k6, k7, k8) ~> (([k2], [k3], [k4], [k5], [k6], [k7], [k8]) ~> ([k2], [k3], [k4], [k5], [k6], [k7], [k8]))) (([k2], [k3], [k4], [k5], [k6], [k7], [k8]) ~> ([(k2, k3, k4, k5, k6, k7, k8)] ~> ([k2], [k3], [k4], [k5], [k6], [k7], [k8]))) -> Type) (Apply (Lambda_6989586621679815205Sym0 :: TyFun [(k2, k3, k4, k5, k6, k7, k8)] (TyFun (k2, k3, k4, k5, k6, k7, k8) (TyFun ([k2], [k3], [k4], [k5], [k6], [k7], [k8]) ([k2], [k3], [k4], [k5], [k6], [k7], [k8]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Apply (Apply (Apply (Apply (Apply (Tuple7Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k5] ~> ([k6] ~> ([k7] ~> ([k8] ~> ([k2], [k3], [k4], [k5], [k6], [k7], [k8]))))))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4])) (NilSym0 :: [k5])) (NilSym0 :: [k6])) (NilSym0 :: [k7])) (NilSym0 :: [k8]))) xs |
sUnzip7 :: forall a b c d e f g (t :: [(a, b, c, d, e, f, g)]). Sing t -> Sing (Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) t) Source #
Special lists
Functions on Symbols
"Set" operations
sNub :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply (NubSym0 :: TyFun [a] [a] -> Type) t) Source #
sDelete :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2) Source #
type family (a1 :: [a]) \\ (a2 :: [a]) :: [a] where ... infix 5 Source #
Equations
| (a_6989586621679815164 :: [a]) \\ (a_6989586621679815166 :: [a]) = Apply (Apply (Apply (FoldlSym0 :: TyFun ([a] ~> (a ~> [a])) ([a] ~> ([a] ~> [a])) -> Type) (Apply (FlipSym0 :: TyFun (a ~> ([a] ~> [a])) ([a] ~> (a ~> [a])) -> Type) (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type))) a_6989586621679815164) a_6989586621679815166 |
(%\\) :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) infix 5 Source #
sUnion :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source #
sIntersect :: forall a (t1 :: [a]) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source #
Ordered lists
sInsert :: forall a (t1 :: a) (t2 :: [a]). SOrd a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) t1) t2) Source #
sSort :: forall a (t :: [a]). SOrd a => Sing t -> Sing (Apply (SortSym0 :: TyFun [a] [a] -> Type) t) Source #
Generalized functions
The "By" operations
User-supplied equality (replacing an Eq context)
The predicate is assumed to define an equivalence.
sNubBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) t1) t2) Source #
sDeleteBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: a) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) t1) t2) t3) Source #
type family DeleteFirstsBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBy (eq :: a ~> (a ~> Bool)) (a_6989586621679815134 :: [a]) (a_6989586621679815136 :: [a]) = Apply (Apply (Apply (FoldlSym0 :: TyFun ([a] ~> (a ~> [a])) ([a] ~> ([a] ~> [a])) -> Type) (Apply (FlipSym0 :: TyFun (a ~> ([a] ~> [a])) ([a] ~> (a ~> [a])) -> Type) (Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) eq))) a_6989586621679815134) a_6989586621679815136 |
sDeleteFirstsBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3) Source #
type family UnionBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ... Source #
Equations
| UnionBy (eq :: a ~> (a ~> Bool)) (xs :: [a]) (ys :: [a]) = Apply (Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) xs) (Apply (Apply (Apply (FoldlSym0 :: TyFun ([a] ~> (a ~> [a])) ([a] ~> ([a] ~> [a])) -> Type) (Apply (FlipSym0 :: TyFun (a ~> ([a] ~> [a])) ([a] ~> (a ~> [a])) -> Type) (Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) eq))) (Apply (Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) eq) ys)) xs) |
sUnionBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3) Source #
type family IntersectBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) (a3 :: [a]) :: [a] where ... Source #
Equations
| IntersectBy (_1 :: a ~> (a ~> Bool)) ('[] :: [a]) ('[] :: [a]) = NilSym0 :: [a] | |
| IntersectBy (_1 :: a ~> (a ~> Bool)) ('[] :: [a]) (_2 ': _3 :: [a]) = NilSym0 :: [a] | |
| IntersectBy (_1 :: a ~> (a ~> Bool)) (_2 ': _3 :: [a]) ('[] :: [a]) = NilSym0 :: [a] | |
| IntersectBy (eq :: b ~> (b ~> Bool)) (wild_6989586621679811554 ': wild_6989586621679811556 :: [b]) (wild_6989586621679811558 ': wild_6989586621679811560 :: [b]) = Apply (Apply ((>>=@#@$) :: TyFun [b] ((b ~> [b]) ~> [b]) -> Type) (Let6989586621679814975XsSym5 eq wild_6989586621679811554 wild_6989586621679811556 wild_6989586621679811558 wild_6989586621679811560)) (Apply (Apply (Apply (Apply (Apply (Lambda_6989586621679814978Sym0 :: TyFun (b ~> (b ~> Bool)) (TyFun b (TyFun [b] (TyFun b (TyFun [b] (TyFun b [b] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) eq) wild_6989586621679811554) wild_6989586621679811556) wild_6989586621679811558) wild_6989586621679811560) |
sIntersectBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) t1) t2) t3) Source #
type family GroupBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) :: [[a]] where ... Source #
Equations
| GroupBy (_1 :: a ~> (a ~> Bool)) ('[] :: [a]) = NilSym0 :: [[a]] | |
| GroupBy (eq :: a ~> (a ~> Bool)) (x ': xs :: [a]) = Apply (Apply ((:@#@$) :: TyFun [a] ([[a]] ~> [[a]]) -> Type) (Apply (Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) x) (Let6989586621679814764YsSym3 eq x xs))) (Apply (Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) eq) (Let6989586621679814764ZsSym3 eq x xs)) |
sGroupBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) t1) t2) Source #
User-supplied comparison (replacing an Ord context)
The function is assumed to define a total ordering.
sSortBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) t1) t2) Source #
type family InsertBy (a1 :: a ~> (a ~> Ordering)) (a2 :: a) (a3 :: [a]) :: [a] where ... Source #
Equations
| InsertBy (_1 :: k1 ~> (k1 ~> Ordering)) (x :: k1) ('[] :: [k1]) = Apply (Apply ((:@#@$) :: TyFun k1 ([k1] ~> [k1]) -> Type) x) (NilSym0 :: [k1]) | |
| InsertBy (cmp :: k1 ~> (k1 ~> Ordering)) (x :: k1) (y ': ys' :: [k1]) = Case_6989586621679815122 cmp x y ys' (Let6989586621679815120Scrutinee_6989586621679811536Sym4 cmp x y ys') |
sInsertBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: a) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) t1) t2) t3) Source #
sMaximumBy :: forall a (t1 :: Type -> Type) (t2 :: a ~> (a ~> Ordering)) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t1 a ~> a) -> Type) t2) t3) Source #
sMinimumBy :: forall a (t1 :: Type -> Type) (t2 :: a ~> (a ~> Ordering)) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t1 a ~> a) -> Type) t2) t3) Source #
The "generic" operations
The prefix `generic' indicates an overloaded function that
is a generalized version of a Prelude function.
type family GenericLength (a1 :: [a]) :: i where ... Source #
Equations
| GenericLength ('[] :: [a]) = FromInteger 0 :: i | |
| GenericLength (_1 ': xs :: [a]) = Apply (Apply ((+@#@$) :: TyFun i (i ~> i) -> Type) (FromInteger 1 :: i)) (Apply (GenericLengthSym0 :: TyFun [a] i -> Type) xs) |
sGenericLength :: forall a i (t :: [a]). SNum i => Sing t -> Sing (Apply (GenericLengthSym0 :: TyFun [a] i -> Type) t) Source #
Defunctionalization symbols
data (:@#@$) (a1 :: TyFun a ([a] ~> [a])) infixr 5 Source #
Instances
| SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679046238 :: a) Source # | |
data (a6989586621679046238 :: a) :@#@$$ (b :: TyFun [a] [a]) infixr 5 Source #
Instances
| SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) (a6989586621679046239 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances | |
type family (a6989586621679046238 :: a) :@#@$$$ (a6989586621679046239 :: [a]) :: [a] where ... infixr 5 Source #
Equations
| (a6989586621679046238 :: a) :@#@$$$ (a6989586621679046239 :: [a]) = a6989586621679046238 ': a6989586621679046239 |
type family (a6989586621679180230 :: [a]) ++@#@$$$ (a6989586621679180231 :: [a]) :: [a] where ... infixr 5 Source #
data (a6989586621679180230 :: [a]) ++@#@$$ (b :: TyFun [a] [a]) infixr 5 Source #
Instances
| SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) (a6989586621679180231 :: [a]) Source # | |
data (++@#@$) (a1 :: TyFun [a] ([a] ~> [a])) infixr 5 Source #
Instances
| SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679180230 :: [a]) Source # | |
data NullSym0 (a1 :: TyFun (t a) Bool) Source #
Instances
| SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
| SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680390432 :: t a) Source # | |
data LengthSym0 (a1 :: TyFun (t a) Natural) Source #
Instances
| SFoldable t => SingI (LengthSym0 :: TyFun (t a) Natural -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Natural -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680390435 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family LengthSym1 (a6989586621680390435 :: t a) :: Natural where ... Source #
Equations
| LengthSym1 (a6989586621680390435 :: t a) = Length a6989586621680390435 |
data MapSym0 (a1 :: TyFun (a ~> b) ([a] ~> [b])) Source #
Instances
| SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
| SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) Source # | |
data MapSym1 (a6989586621679180239 :: a ~> b) (b1 :: TyFun [a] [b]) Source #
Instances
| SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # | |
| SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) (a6989586621679180240 :: [a]) Source # | |
type family MapSym2 (a6989586621679180239 :: a ~> b) (a6989586621679180240 :: [a]) :: [b] where ... Source #
data ReverseSym0 (a1 :: TyFun [a] [a]) Source #
Instances
| SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ReverseSym0 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679815786 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679815786 :: [a]) = Reverse a6989586621679815786 | |
type family ReverseSym1 (a6989586621679815786 :: [a]) :: [a] where ... Source #
Equations
| ReverseSym1 (a6989586621679815786 :: [a]) = Reverse a6989586621679815786 |
data IntersperseSym0 (a1 :: TyFun a ([a] ~> [a])) Source #
Instances
| SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815779 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815779 :: a) = IntersperseSym1 a6989586621679815779 | |
data IntersperseSym1 (a6989586621679815779 :: a) (b :: TyFun [a] [a]) Source #
Instances
| SingI1 (IntersperseSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) # | |
| SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersperseSym1 d) # | |
| SuppressUnusedWarnings (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) (a6989586621679815780 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) (a6989586621679815780 :: [a]) = Intersperse a6989586621679815779 a6989586621679815780 | |
type family IntersperseSym2 (a6989586621679815779 :: a) (a6989586621679815780 :: [a]) :: [a] where ... Source #
Equations
| IntersperseSym2 (a6989586621679815779 :: a) (a6989586621679815780 :: [a]) = Intersperse a6989586621679815779 a6989586621679815780 |
data IntercalateSym0 (a1 :: TyFun [a] ([[a]] ~> [a])) Source #
Instances
| SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679815772 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679815772 :: [a]) = IntercalateSym1 a6989586621679815772 | |
data IntercalateSym1 (a6989586621679815772 :: [a]) (b :: TyFun [[a]] [a]) Source #
Instances
| SingI1 (IntercalateSym1 :: [a] -> TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IntercalateSym1 x) # | |
| SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntercalateSym1 d) # | |
| SuppressUnusedWarnings (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) (a6989586621679815773 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) (a6989586621679815773 :: [[a]]) = Intercalate a6989586621679815772 a6989586621679815773 | |
type family IntercalateSym2 (a6989586621679815772 :: [a]) (a6989586621679815773 :: [[a]]) :: [a] where ... Source #
Equations
| IntercalateSym2 (a6989586621679815772 :: [a]) (a6989586621679815773 :: [[a]]) = Intercalate a6989586621679815772 a6989586621679815773 |
data TransposeSym0 (a1 :: TyFun [[a]] [[a]]) Source #
Instances
| SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679814673 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679814673 :: [[a]]) = Transpose a6989586621679814673 | |
type family TransposeSym1 (a6989586621679814673 :: [[a]]) :: [[a]] where ... Source #
Equations
| TransposeSym1 (a6989586621679814673 :: [[a]]) = Transpose a6989586621679814673 |
data SubsequencesSym0 (a1 :: TyFun [a] [[a]]) Source #
Instances
| SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679815767 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679815767 :: [a]) = Subsequences a6989586621679815767 | |
type family SubsequencesSym1 (a6989586621679815767 :: [a]) :: [[a]] where ... Source #
Equations
| SubsequencesSym1 (a6989586621679815767 :: [a]) = Subsequences a6989586621679815767 |
data PermutationsSym0 (a1 :: TyFun [a] [[a]]) Source #
Instances
| SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679815693 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679815693 :: [a]) = Permutations a6989586621679815693 | |
type family PermutationsSym1 (a6989586621679815693 :: [a]) :: [[a]] where ... Source #
Equations
| PermutationsSym1 (a6989586621679815693 :: [a]) = Permutations a6989586621679815693 |
data FoldlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b))) Source #
Instances
| SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
| SuppressUnusedWarnings (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) Source # | |
data FoldlSym1 (a6989586621680390407 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b)) Source #
Instances
| SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
| SuppressUnusedWarnings (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) Source # | |
data FoldlSym2 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (c :: TyFun (t a) b) Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
| SFoldable t => SingI2 (FoldlSym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
| (SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
| SuppressUnusedWarnings (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) (a6989586621680390409 :: t a) Source # | |
type family FoldlSym3 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (a6989586621680390409 :: t a) :: b where ... Source #
data Foldl'Sym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b))) Source #
Instances
| SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
| SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390414 :: b ~> (a ~> b)) Source # | |
Defined in Data.Foldable.Singletons | |
data Foldl'Sym1 (a6989586621680390414 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b)) Source #
Instances
| SFoldable t => SingI1 (Foldl'Sym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) = Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type | |
data Foldl'Sym2 (a6989586621680390414 :: b ~> (a ~> b)) (a6989586621680390415 :: b) (c :: TyFun (t a) b) Source #
Instances
| (SFoldable t, SingI d) => SingI1 (Foldl'Sym2 d :: b -> TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SFoldable t => SingI2 (Foldl'Sym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
| (SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) (a6989586621680390416 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) (a6989586621680390416 :: t a) = Foldl' a6989586621680390414 a6989586621680390415 a6989586621680390416 | |
type family Foldl'Sym3 (a6989586621680390414 :: b ~> (a ~> b)) (a6989586621680390415 :: b) (a6989586621680390416 :: t a) :: b where ... Source #
Equations
| Foldl'Sym3 (a6989586621680390414 :: b ~> (a ~> b)) (a6989586621680390415 :: b) (a6989586621680390416 :: t a) = Foldl' a6989586621680390414 a6989586621680390415 a6989586621680390416 |
data Foldl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a)) Source #
Instances
| SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons | |
data Foldl1Sym1 (a6989586621680390425 :: a ~> (a ~> a)) (b :: TyFun (t a) a) Source #
Instances
| SFoldable t => SingI1 (Foldl1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) = Foldl1 a6989586621680390425 a6989586621680390426 | |
type family Foldl1Sym2 (a6989586621680390425 :: a ~> (a ~> a)) (a6989586621680390426 :: t a) :: a where ... Source #
Equations
| Foldl1Sym2 (a6989586621680390425 :: a ~> (a ~> a)) (a6989586621680390426 :: t a) = Foldl1 a6989586621680390425 a6989586621680390426 |
data Foldl1'Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> a)) Source #
Instances
| SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679815658 | |
data Foldl1'Sym1 (a6989586621679815658 :: a ~> (a ~> a)) (b :: TyFun [a] a) Source #
Instances
| SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Foldl1'Sym1 d) # | |
| SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679815658 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Foldl1'Sym1 :: (a ~> (a ~> a)) -> TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (Foldl1'Sym1 a6989586621679815658 :: TyFun [a] a -> Type) (a6989586621679815659 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym1 a6989586621679815658 :: TyFun [a] a -> Type) (a6989586621679815659 :: [a]) = Foldl1' a6989586621679815658 a6989586621679815659 | |
type family Foldl1'Sym2 (a6989586621679815658 :: a ~> (a ~> a)) (a6989586621679815659 :: [a]) :: a where ... Source #
Equations
| Foldl1'Sym2 (a6989586621679815658 :: a ~> (a ~> a)) (a6989586621679815659 :: [a]) = Foldl1' a6989586621679815658 a6989586621679815659 |
data FoldrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b))) Source #
Instances
| SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
| SuppressUnusedWarnings (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) Source # | |
data FoldrSym1 (a6989586621680390393 :: a ~> (b ~> b)) (b1 :: TyFun b (t a ~> b)) Source #
Instances
| SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # | |
| SuppressUnusedWarnings (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) Source # | |
data FoldrSym2 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (c :: TyFun (t a) b) Source #
Instances
| (SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # | |
| SFoldable t => SingI2 (FoldrSym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # | |
| (SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # | |
| SuppressUnusedWarnings (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) (a6989586621680390395 :: t a) Source # | |
type family FoldrSym3 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (a6989586621680390395 :: t a) :: b where ... Source #
data Foldr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a)) Source #
Instances
| SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons | |
data Foldr1Sym1 (a6989586621680390420 :: a ~> (a ~> a)) (b :: TyFun (t a) a) Source #
Instances
| SFoldable t => SingI1 (Foldr1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) = Foldr1 a6989586621680390420 a6989586621680390421 | |
type family Foldr1Sym2 (a6989586621680390420 :: a ~> (a ~> a)) (a6989586621680390421 :: t a) :: a where ... Source #
Equations
| Foldr1Sym2 (a6989586621680390420 :: a ~> (a ~> a)) (a6989586621680390421 :: t a) = Foldr1 a6989586621680390420 a6989586621680390421 |
data ConcatSym0 (a1 :: TyFun (t [a]) [a]) Source #
Instances
| SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680390274 :: t [a]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680390274 :: t [a]) = Concat a6989586621680390274 | |
type family ConcatSym1 (a6989586621680390274 :: t [a]) :: [a] where ... Source #
Equations
| ConcatSym1 (a6989586621680390274 :: t [a]) = Concat a6989586621680390274 |
data ConcatMapSym0 (a1 :: TyFun (a ~> [b]) (t a ~> [b])) Source #
Instances
| SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) = ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type | |
data ConcatMapSym1 (a6989586621680390263 :: a ~> [b]) (b1 :: TyFun (t a) [b]) Source #
Instances
| SFoldable t => SingI1 (ConcatMapSym1 :: (a ~> [b]) -> TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) = ConcatMap a6989586621680390263 a6989586621680390264 | |
type family ConcatMapSym2 (a6989586621680390263 :: a ~> [b]) (a6989586621680390264 :: t a) :: [b] where ... Source #
Equations
| ConcatMapSym2 (a6989586621680390263 :: a ~> [b]) (a6989586621680390264 :: t a) = ConcatMap a6989586621680390263 a6989586621680390264 |
data AndSym0 (a :: TyFun (t Bool) Bool) Source #
Instances
| SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
| SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680390258 :: t Bool) Source # | |
data OrSym0 (a :: TyFun (t Bool) Bool) Source #
Instances
| SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
| SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680390252 :: t Bool) Source # | |
data AnySym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool)) Source #
Instances
| SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
| SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) Source # | |
data AnySym1 (a6989586621680390244 :: a ~> Bool) (b :: TyFun (t a) Bool) Source #
Instances
| SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # | |
| SuppressUnusedWarnings (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) (a6989586621680390245 :: t a) Source # | |
type family AnySym2 (a6989586621680390244 :: a ~> Bool) (a6989586621680390245 :: t a) :: Bool where ... Source #
data AllSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool)) Source #
Instances
| SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
| SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) Source # | |
data AllSym1 (a6989586621680390235 :: a ~> Bool) (b :: TyFun (t a) Bool) Source #
Instances
| SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # | |
| SuppressUnusedWarnings (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) (a6989586621680390236 :: t a) Source # | |
type family AllSym2 (a6989586621680390235 :: a ~> Bool) (a6989586621680390236 :: t a) :: Bool where ... Source #
data SumSym0 (a1 :: TyFun (t a) a) Source #
Instances
| (SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # | |
| SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680390449 :: t a) Source # | |
data ProductSym0 (a1 :: TyFun (t a) a) Source #
Instances
| (SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680390452 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680390452 :: t a) = Product a6989586621680390452 | |
type family ProductSym1 (a6989586621680390452 :: t a) :: a where ... Source #
Equations
| ProductSym1 (a6989586621680390452 :: t a) = Product a6989586621680390452 |
data MaximumSym0 (a1 :: TyFun (t a) a) Source #
Instances
| (SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680390443 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680390443 :: t a) = Maximum a6989586621680390443 | |
type family MaximumSym1 (a6989586621680390443 :: t a) :: a where ... Source #
Equations
| MaximumSym1 (a6989586621680390443 :: t a) = Maximum a6989586621680390443 |
data MinimumSym0 (a1 :: TyFun (t a) a) Source #
Instances
| (SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680390446 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680390446 :: t a) = Minimum a6989586621680390446 | |
type family MinimumSym1 (a6989586621680390446 :: t a) :: a where ... Source #
Equations
| MinimumSym1 (a6989586621680390446 :: t a) = Minimum a6989586621680390446 |
data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b]))) Source #
Instances
| SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
| SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621679815591 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> [b])) Source #
Instances
| SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) Source # | |
data ScanlSym2 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (c :: TyFun [a] [b]) Source #
Instances
| SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
| SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] [b] -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) (a6989586621679815593 :: [a]) Source # | |
type family ScanlSym3 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (a6989586621679815593 :: [a]) :: [b] where ... Source #
data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a])) Source #
Instances
| SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679815582 | |
data Scanl1Sym1 (a6989586621679815582 :: a ~> (a ~> a)) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Scanl1Sym1 d) # | |
| SuppressUnusedWarnings (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) = Scanl1 a6989586621679815582 a6989586621679815583 | |
type family Scanl1Sym2 (a6989586621679815582 :: a ~> (a ~> a)) (a6989586621679815583 :: [a]) :: [a] where ... Source #
Equations
| Scanl1Sym2 (a6989586621679815582 :: a ~> (a ~> a)) (a6989586621679815583 :: [a]) = Scanl1 a6989586621679815582 a6989586621679815583 |
data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b]))) Source #
Instances
| SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
| SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621679815564 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> [b])) Source #
Instances
| SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # | |
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) Source # | |
data ScanrSym2 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (c :: TyFun [a] [b]) Source #
Instances
| SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # | |
| SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] [b] -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) (a6989586621679815566 :: [a]) Source # | |
type family ScanrSym3 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (a6989586621679815566 :: [a]) :: [b] where ... Source #
data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a])) Source #
Instances
| SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679815544 | |
data Scanr1Sym1 (a6989586621679815544 :: a ~> (a ~> a)) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (Scanr1Sym1 d) # | |
| SuppressUnusedWarnings (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) = Scanr1 a6989586621679815544 a6989586621679815545 | |
type family Scanr1Sym2 (a6989586621679815544 :: a ~> (a ~> a)) (a6989586621679815545 :: [a]) :: [a] where ... Source #
Equations
| Scanr1Sym2 (a6989586621679815544 :: a ~> (a ~> a)) (a6989586621679815545 :: [a]) = Scanr1 a6989586621679815544 a6989586621679815545 |
data MapAccumLSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c)))) Source #
Instances
| STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
| SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741278 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons | |
data MapAccumLSym1 (a6989586621680741278 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c))) Source #
Instances
| STraversable t => SingI1 (MapAccumLSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
| (STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| SuppressUnusedWarnings (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) = MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumLSym2 (a6989586621680741278 :: a ~> (b ~> (a, c))) (a6989586621680741279 :: a) (c1 :: TyFun (t b) (a, t c)) Source #
Instances
| (STraversable t, SingI d) => SingI1 (MapAccumLSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| STraversable t => SingI2 (MapAccumLSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
| (STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| SuppressUnusedWarnings (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741280 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741280 :: t b) = MapAccumL a6989586621680741278 a6989586621680741279 a6989586621680741280 | |
type family MapAccumLSym3 (a6989586621680741278 :: a ~> (b ~> (a, c))) (a6989586621680741279 :: a) (a6989586621680741280 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumLSym3 (a6989586621680741278 :: a ~> (b ~> (a, c))) (a6989586621680741279 :: a) (a6989586621680741280 :: t b) = MapAccumL a6989586621680741278 a6989586621680741279 a6989586621680741280 |
data MapAccumRSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c)))) Source #
Instances
| STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
| SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741268 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons | |
data MapAccumRSym1 (a6989586621680741268 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c))) Source #
Instances
| STraversable t => SingI1 (MapAccumRSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # | |
| (STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| SuppressUnusedWarnings (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) = MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type | |
data MapAccumRSym2 (a6989586621680741268 :: a ~> (b ~> (a, c))) (a6989586621680741269 :: a) (c1 :: TyFun (t b) (a, t c)) Source #
Instances
| (STraversable t, SingI d) => SingI1 (MapAccumRSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| STraversable t => SingI2 (MapAccumRSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # | |
| (STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons | |
| SuppressUnusedWarnings (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741270 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741270 :: t b) = MapAccumR a6989586621680741268 a6989586621680741269 a6989586621680741270 | |
type family MapAccumRSym3 (a6989586621680741268 :: a ~> (b ~> (a, c))) (a6989586621680741269 :: a) (a6989586621680741270 :: t b) :: (a, t c) where ... Source #
Equations
| MapAccumRSym3 (a6989586621680741268 :: a ~> (b ~> (a, c))) (a6989586621680741269 :: a) (a6989586621680741270 :: t b) = MapAccumR a6989586621680741268 a6989586621680741269 a6989586621680741270 |
data ReplicateSym0 (a1 :: TyFun Natural (a ~> [a])) Source #
Instances
| SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679814681 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679814681 :: Natural) = ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type | |
data ReplicateSym1 (a6989586621679814681 :: Natural) (b :: TyFun a [a]) Source #
Instances
| SingI1 (ReplicateSym1 :: Natural -> TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) = Replicate a6989586621679814681 a6989586621679814682 | |
type family ReplicateSym2 (a6989586621679814681 :: Natural) (a6989586621679814682 :: a) :: [a] where ... Source #
Equations
| ReplicateSym2 a6989586621679814681 (a6989586621679814682 :: a) = Replicate a6989586621679814681 a6989586621679814682 |
data UnfoldrSym0 (a1 :: TyFun (b ~> Maybe (a, b)) (b ~> [a])) Source #
Instances
| SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679815436 | |
data UnfoldrSym1 (a6989586621679815436 :: b ~> Maybe (a, b)) (b1 :: TyFun b [a]) Source #
Instances
| SingI1 (UnfoldrSym1 :: (b ~> Maybe (a, b)) -> TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnfoldrSym1 d) # | |
| SuppressUnusedWarnings (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) (a6989586621679815437 :: b) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) (a6989586621679815437 :: b) = Unfoldr a6989586621679815436 a6989586621679815437 | |
type family UnfoldrSym2 (a6989586621679815436 :: b ~> Maybe (a, b)) (a6989586621679815437 :: b) :: [a] where ... Source #
Equations
| UnfoldrSym2 (a6989586621679815436 :: b ~> Maybe (a, b)) (a6989586621679815437 :: b) = Unfoldr a6989586621679815436 a6989586621679815437 |
data TakeSym0 (a1 :: TyFun Natural ([a] ~> [a])) Source #
Instances
| SingI (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679814836 :: Natural) Source # | |
data TakeSym1 (a6989586621679814836 :: Natural) (b :: TyFun [a] [a]) Source #
Instances
| SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # | |
| SuppressUnusedWarnings (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) (a6989586621679814837 :: [a]) Source # | |
type family TakeSym2 (a6989586621679814836 :: Natural) (a6989586621679814837 :: [a]) :: [a] where ... Source #
data DropSym0 (a1 :: TyFun Natural ([a] ~> [a])) Source #
Instances
| SingI (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679814823 :: Natural) Source # | |
data DropSym1 (a6989586621679814823 :: Natural) (b :: TyFun [a] [a]) Source #
Instances
| SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # | |
| SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # | |
| SuppressUnusedWarnings (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) (a6989586621679814824 :: [a]) Source # | |
type family DropSym2 (a6989586621679814823 :: Natural) (a6989586621679814824 :: [a]) :: [a] where ... Source #
data SplitAtSym0 (a1 :: TyFun Natural ([a] ~> ([a], [a]))) Source #
Instances
| SingI (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679814816 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679814816 :: Natural) = SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type | |
data SplitAtSym1 (a6989586621679814816 :: Natural) (b :: TyFun [a] ([a], [a])) Source #
Instances
| SingI1 (SplitAtSym1 :: Natural -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) = SplitAt a6989586621679814816 a6989586621679814817 | |
type family SplitAtSym2 (a6989586621679814816 :: Natural) (a6989586621679814817 :: [a]) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621679814816 (a6989586621679814817 :: [a]) = SplitAt a6989586621679814816 a6989586621679814817 |
data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #
Instances
| SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) = TakeWhileSym1 a6989586621679814953 | |
data TakeWhileSym1 (a6989586621679814953 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (TakeWhileSym1 d) # | |
| SuppressUnusedWarnings (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) = TakeWhile a6989586621679814953 a6989586621679814954 | |
type family TakeWhileSym2 (a6989586621679814953 :: a ~> Bool) (a6989586621679814954 :: [a]) :: [a] where ... Source #
Equations
| TakeWhileSym2 (a6989586621679814953 :: a ~> Bool) (a6989586621679814954 :: [a]) = TakeWhile a6989586621679814953 a6989586621679814954 |
data DropWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #
Instances
| SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) = DropWhileSym1 a6989586621679814938 | |
data DropWhileSym1 (a6989586621679814938 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DropWhileSym1 d) # | |
| SuppressUnusedWarnings (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) = DropWhile a6989586621679814938 a6989586621679814939 | |
type family DropWhileSym2 (a6989586621679814938 :: a ~> Bool) (a6989586621679814939 :: [a]) :: [a] where ... Source #
Equations
| DropWhileSym2 (a6989586621679814938 :: a ~> Bool) (a6989586621679814939 :: [a]) = DropWhile a6989586621679814938 a6989586621679814939 |
data DropWhileEndSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #
Instances
| SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) = DropWhileEndSym1 a6989586621679814921 | |
data DropWhileEndSym1 (a6989586621679814921 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DropWhileEndSym1 d) # | |
| SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) = DropWhileEnd a6989586621679814921 a6989586621679814922 | |
type family DropWhileEndSym2 (a6989586621679814921 :: a ~> Bool) (a6989586621679814922 :: [a]) :: [a] where ... Source #
Equations
| DropWhileEndSym2 (a6989586621679814921 :: a ~> Bool) (a6989586621679814922 :: [a]) = DropWhileEnd a6989586621679814921 a6989586621679814922 |
data SpanSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a]))) Source #
Instances
| SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
| SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621679814884 :: a ~> Bool) (b :: TyFun [a] ([a], [a])) Source #
Instances
| SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
| type Apply (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814885 :: [a]) Source # | |
type family SpanSym2 (a6989586621679814884 :: a ~> Bool) (a6989586621679814885 :: [a]) :: ([a], [a]) where ... Source #
data BreakSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a]))) Source #
Instances
| SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
| SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621679814849 :: a ~> Bool) (b :: TyFun [a] ([a], [a])) Source #
Instances
| SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
| type Apply (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814850 :: [a]) Source # | |
type family BreakSym2 (a6989586621679814849 :: a ~> Bool) (a6989586621679814850 :: [a]) :: ([a], [a]) where ... Source #
data StripPrefixSym0 (a1 :: TyFun [a] ([a] ~> Maybe [a])) Source #
Instances
| SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679966032 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679966032 :: [a]) = StripPrefixSym1 a6989586621679966032 | |
data StripPrefixSym1 (a6989586621679966032 :: [a]) (b :: TyFun [a] (Maybe [a])) Source #
Instances
| SuppressUnusedWarnings (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679966033 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679966033 :: [a]) = StripPrefix a6989586621679966032 a6989586621679966033 | |
type family StripPrefixSym2 (a6989586621679966032 :: [a]) (a6989586621679966033 :: [a]) :: Maybe [a] where ... Source #
Equations
| StripPrefixSym2 (a6989586621679966032 :: [a]) (a6989586621679966033 :: [a]) = StripPrefix a6989586621679966032 a6989586621679966033 |
data GroupSym0 (a1 :: TyFun [a] [[a]]) Source #
Instances
| SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
| SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679814811 :: [a]) Source # | |
data InitsSym0 (a1 :: TyFun [a] [[a]]) Source #
Instances
data TailsSym0 (a1 :: TyFun [a] [[a]]) Source #
Instances
data IsPrefixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool)) Source #
Instances
| SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815410 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815410 :: [a]) = IsPrefixOfSym1 a6989586621679815410 | |
data IsPrefixOfSym1 (a6989586621679815410 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
| SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) # | |
| (SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsPrefixOfSym1 d) # | |
| SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) (a6989586621679815411 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) (a6989586621679815411 :: [a]) = IsPrefixOf a6989586621679815410 a6989586621679815411 | |
type family IsPrefixOfSym2 (a6989586621679815410 :: [a]) (a6989586621679815411 :: [a]) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 (a6989586621679815410 :: [a]) (a6989586621679815411 :: [a]) = IsPrefixOf a6989586621679815410 a6989586621679815411 |
data IsSuffixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool)) Source #
Instances
| SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815403 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815403 :: [a]) = IsSuffixOfSym1 a6989586621679815403 | |
data IsSuffixOfSym1 (a6989586621679815403 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
| SEq a => SingI1 (IsSuffixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IsSuffixOfSym1 x) # | |
| (SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsSuffixOfSym1 d) # | |
| SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) (a6989586621679815404 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) (a6989586621679815404 :: [a]) = IsSuffixOf a6989586621679815403 a6989586621679815404 | |
type family IsSuffixOfSym2 (a6989586621679815403 :: [a]) (a6989586621679815404 :: [a]) :: Bool where ... Source #
Equations
| IsSuffixOfSym2 (a6989586621679815403 :: [a]) (a6989586621679815404 :: [a]) = IsSuffixOf a6989586621679815403 a6989586621679815404 |
data IsInfixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool)) Source #
Instances
| SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815396 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679815396 :: [a]) = IsInfixOfSym1 a6989586621679815396 | |
data IsInfixOfSym1 (a6989586621679815396 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
| SEq a => SingI1 (IsInfixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IsInfixOfSym1 x) # | |
| (SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IsInfixOfSym1 d) # | |
| SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679815396 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IsInfixOfSym1 a6989586621679815396 :: TyFun [a] Bool -> Type) (a6989586621679815397 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family IsInfixOfSym2 (a6989586621679815396 :: [a]) (a6989586621679815397 :: [a]) :: Bool where ... Source #
Equations
| IsInfixOfSym2 (a6989586621679815396 :: [a]) (a6989586621679815397 :: [a]) = IsInfixOf a6989586621679815396 a6989586621679815397 |
data ElemSym0 (a1 :: TyFun a (t a ~> Bool)) Source #
Instances
| (SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
| SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390439 :: a) Source # | |
data ElemSym1 (a6989586621680390439 :: a) (b :: TyFun (t a) Bool) Source #
Instances
| (SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # | |
| (SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
| SuppressUnusedWarnings (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) (a6989586621680390440 :: t a) Source # | |
type family ElemSym2 (a6989586621680390439 :: a) (a6989586621680390440 :: t a) :: Bool where ... Source #
data NotElemSym0 (a1 :: TyFun a (t a ~> Bool)) Source #
Instances
| (SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390186 :: a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390186 :: a) = NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type | |
data NotElemSym1 (a6989586621680390186 :: a) (b :: TyFun (t a) Bool) Source #
Instances
| (SFoldable t, SEq a) => SingI1 (NotElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| (SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) (a6989586621680390187 :: t a) Source # | |
Defined in Data.Foldable.Singletons | |
type family NotElemSym2 (a6989586621680390186 :: a) (a6989586621680390187 :: t a) :: Bool where ... Source #
Equations
| NotElemSym2 (a6989586621680390186 :: a) (a6989586621680390187 :: t a) = NotElem a6989586621680390186 a6989586621680390187 |
data LookupSym0 (a1 :: TyFun a ([(a, b)] ~> Maybe b)) Source #
Instances
| SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679814744 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679814744 :: a) = LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type | |
data LookupSym1 (a6989586621679814744 :: a) (b1 :: TyFun [(a, b)] (Maybe b)) Source #
Instances
| SEq a => SingI1 (LookupSym1 :: a -> TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679814745 :: [(a, b)]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family LookupSym2 (a6989586621679814744 :: a) (a6989586621679814745 :: [(a, b)]) :: Maybe b where ... Source #
Equations
| LookupSym2 (a6989586621679814744 :: a) (a6989586621679814745 :: [(a, b)]) = Lookup a6989586621679814744 a6989586621679814745 |
data FindSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Maybe a)) Source #
Instances
| SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
| SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680390168 :: a ~> Bool) Source # | |
data FindSym1 (a6989586621680390168 :: a ~> Bool) (b :: TyFun (t a) (Maybe a)) Source #
Instances
| SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # | |
| SuppressUnusedWarnings (FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680390169 :: t a) Source # | |
type family FindSym2 (a6989586621680390168 :: a ~> Bool) (a6989586621680390169 :: t a) :: Maybe a where ... Source #
data FilterSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #
Instances
| SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) = FilterSym1 a6989586621679815053 | |
data FilterSym1 (a6989586621679815053 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FilterSym1 d) # | |
| SuppressUnusedWarnings (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) = Filter a6989586621679815053 a6989586621679815054 | |
type family FilterSym2 (a6989586621679815053 :: a ~> Bool) (a6989586621679815054 :: [a]) :: [a] where ... Source #
Equations
| FilterSym2 (a6989586621679815053 :: a ~> Bool) (a6989586621679815054 :: [a]) = Filter a6989586621679815053 a6989586621679815054 |
data PartitionSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a]))) Source #
Instances
| SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) = PartitionSym1 a6989586621679814737 | |
data PartitionSym1 (a6989586621679814737 :: a ~> Bool) (b :: TyFun [a] ([a], [a])) Source #
Instances
| SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (PartitionSym1 d) # | |
| SuppressUnusedWarnings (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814738 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814738 :: [a]) = Partition a6989586621679814737 a6989586621679814738 | |
type family PartitionSym2 (a6989586621679814737 :: a ~> Bool) (a6989586621679814738 :: [a]) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 (a6989586621679814737 :: a ~> Bool) (a6989586621679814738 :: [a]) = Partition a6989586621679814737 a6989586621679814738 |
data (!!@#@$) (a1 :: TyFun [a] (Natural ~> a)) infixl 9 Source #
Instances
| SingI ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # | |
| SuppressUnusedWarnings ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679814661 :: [a]) Source # | |
data (a6989586621679814661 :: [a]) !!@#@$$ (b :: TyFun Natural a) infixl 9 Source #
Instances
| SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # | |
| SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) (a6989586621679814662 :: Natural) Source # | |
type family (a6989586621679814661 :: [a]) !!@#@$$$ (a6989586621679814662 :: Natural) :: a where ... infixl 9 Source #
data ElemIndexSym0 (a1 :: TyFun a ([a] ~> Maybe Natural)) Source #
Instances
| SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679815037 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679815037 :: a) = ElemIndexSym1 a6989586621679815037 | |
data ElemIndexSym1 (a6989586621679815037 :: a) (b :: TyFun [a] (Maybe Natural)) Source #
Instances
| SEq a => SingI1 (ElemIndexSym1 :: a -> TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (ElemIndexSym1 x) # | |
| (SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ElemIndexSym1 d) # | |
| SuppressUnusedWarnings (ElemIndexSym1 a6989586621679815037 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndexSym1 a6989586621679815037 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815038 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family ElemIndexSym2 (a6989586621679815037 :: a) (a6989586621679815038 :: [a]) :: Maybe Natural where ... Source #
Equations
| ElemIndexSym2 (a6989586621679815037 :: a) (a6989586621679815038 :: [a]) = ElemIndex a6989586621679815037 a6989586621679815038 |
data ElemIndicesSym0 (a1 :: TyFun a ([a] ~> [Natural])) Source #
Instances
| SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679815028 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679815028 :: a) = ElemIndicesSym1 a6989586621679815028 | |
data ElemIndicesSym1 (a6989586621679815028 :: a) (b :: TyFun [a] [Natural]) Source #
Instances
| SEq a => SingI1 (ElemIndicesSym1 :: a -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (ElemIndicesSym1 x) # | |
| (SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ElemIndicesSym1 d) # | |
| SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) (a6989586621679815029 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) (a6989586621679815029 :: [a]) = ElemIndices a6989586621679815028 a6989586621679815029 | |
type family ElemIndicesSym2 (a6989586621679815028 :: a) (a6989586621679815029 :: [a]) :: [Natural] where ... Source #
Equations
| ElemIndicesSym2 (a6989586621679815028 :: a) (a6989586621679815029 :: [a]) = ElemIndices a6989586621679815028 a6989586621679815029 |
data FindIndexSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural)) Source #
Instances
| SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # | |
| SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679815019 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal | |
data FindIndexSym1 (a6989586621679815019 :: a ~> Bool) (b :: TyFun [a] (Maybe Natural)) Source #
Instances
| SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FindIndexSym1 d) # | |
| SuppressUnusedWarnings (FindIndexSym1 a6989586621679815019 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FindIndexSym1 :: (a ~> Bool) -> TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (FindIndexSym1 a6989586621679815019 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815020 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family FindIndexSym2 (a6989586621679815019 :: a ~> Bool) (a6989586621679815020 :: [a]) :: Maybe Natural where ... Source #
Equations
| FindIndexSym2 (a6989586621679815019 :: a ~> Bool) (a6989586621679815020 :: [a]) = FindIndex a6989586621679815019 a6989586621679815020 |
data FindIndicesSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [Natural])) Source #
Instances
| SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # | |
| SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679814996 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal | |
data FindIndicesSym1 (a6989586621679814996 :: a ~> Bool) (b :: TyFun [a] [Natural]) Source #
Instances
| SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (FindIndicesSym1 d) # | |
| SuppressUnusedWarnings (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (FindIndicesSym1 :: (a ~> Bool) -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) (a6989586621679814997 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) (a6989586621679814997 :: [a]) = FindIndices a6989586621679814996 a6989586621679814997 | |
type family FindIndicesSym2 (a6989586621679814996 :: a ~> Bool) (a6989586621679814997 :: [a]) :: [Natural] where ... Source #
Equations
| FindIndicesSym2 (a6989586621679814996 :: a ~> Bool) (a6989586621679814997 :: [a]) = FindIndices a6989586621679814996 a6989586621679814997 |
data ZipSym0 (a1 :: TyFun [a] ([b] ~> [(a, b)])) Source #
Instances
| SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
| SuppressUnusedWarnings (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) Source # | |
data ZipSym1 (a6989586621679815371 :: [a]) (b1 :: TyFun [b] [(a, b)]) Source #
Instances
| SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # | |
| SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # | |
| SuppressUnusedWarnings (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) (a6989586621679815372 :: [b]) Source # | |
type family ZipSym2 (a6989586621679815371 :: [a]) (a6989586621679815372 :: [b]) :: [(a, b)] where ... Source #
data Zip3Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)]))) Source #
Instances
| SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
| SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) Source # | |
data Zip3Sym1 (a6989586621679815359 :: [a]) (b1 :: TyFun [b] ([c] ~> [(a, b, c)])) Source #
Instances
| SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
| SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
| SuppressUnusedWarnings (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) Source # | |
data Zip3Sym2 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (c1 :: TyFun [c] [(a, b, c)]) Source #
Instances
| SingI2 (Zip3Sym2 :: [a] -> [b] -> TyFun [c] [(a, b, c)] -> Type) Source # | |
| SingI d => SingI1 (Zip3Sym2 d :: [b] -> TyFun [c] [(a, b, c)] -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
| SuppressUnusedWarnings (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679815361 :: [c]) Source # | |
type family Zip3Sym3 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (a6989586621679815361 :: [c]) :: [(a, b, c)] where ... Source #
data Zip4Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)])))) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679966021 :: [a]) Source # | |
data Zip4Sym1 (a6989586621679966021 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)]))) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679966022 :: [b]) Source # | |
data Zip4Sym2 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (c1 :: TyFun [c] ([d] ~> [(a, b, c, d)])) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679966023 :: [c]) Source # | |
data Zip4Sym3 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (a6989586621679966023 :: [c]) (d1 :: TyFun [d] [(a, b, c, d)]) Source #
Instances
| SuppressUnusedWarnings (Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679966024 :: [d]) Source # | |
type family Zip4Sym4 (a6989586621679966021 :: [a]) (a6989586621679966022 :: [b]) (a6989586621679966023 :: [c]) (a6989586621679966024 :: [d]) :: [(a, b, c, d)] where ... Source #
data Zip5Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679965998 :: [a]) Source # | |
data Zip5Sym1 (a6989586621679965998 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679965999 :: [b]) Source # | |
data Zip5Sym2 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)]))) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679966000 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym3 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (d1 :: TyFun [d] ([e] ~> [(a, b, c, d, e)])) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679966001 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip5Sym4 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (a6989586621679966001 :: [d]) (e1 :: TyFun [e] [(a, b, c, d, e)]) Source #
Instances
| SuppressUnusedWarnings (Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679966002 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family Zip5Sym5 (a6989586621679965998 :: [a]) (a6989586621679965999 :: [b]) (a6989586621679966000 :: [c]) (a6989586621679966001 :: [d]) (a6989586621679966002 :: [e]) :: [(a, b, c, d, e)] where ... Source #
data Zip6Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679965970 :: [a]) Source # | |
data Zip6Sym1 (a6989586621679965970 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679965971 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym2 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679965972 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip6Sym3 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) = Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type | |
data Zip6Sym4 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (e1 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)])) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) = Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type | |
data Zip6Sym5 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (a6989586621679965974 :: [e]) (f1 :: TyFun [f] [(a, b, c, d, e, f)]) Source #
Instances
| SuppressUnusedWarnings (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679965975 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679965975 :: [f]) = Zip6 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 a6989586621679965975 | |
type family Zip6Sym6 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (a6989586621679965974 :: [e]) (a6989586621679965975 :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Equations
| Zip6Sym6 (a6989586621679965970 :: [a]) (a6989586621679965971 :: [b]) (a6989586621679965972 :: [c]) (a6989586621679965973 :: [d]) (a6989586621679965974 :: [e]) (a6989586621679965975 :: [f]) = Zip6 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 a6989586621679965975 |
data Zip7Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679965937 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym1 (a6989586621679965937 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679965938 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal | |
data Zip7Sym2 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) = Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type | |
data Zip7Sym3 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) = Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type | |
data Zip7Sym4 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (e1 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) = Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type | |
data Zip7Sym5 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (f1 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)])) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) = Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type | |
data Zip7Sym6 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (a6989586621679965942 :: [f]) (g1 :: TyFun [g] [(a, b, c, d, e, f, g)]) Source #
Instances
| SuppressUnusedWarnings (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679965943 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679965943 :: [g]) = Zip7 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 a6989586621679965943 | |
type family Zip7Sym7 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (a6989586621679965942 :: [f]) (a6989586621679965943 :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Equations
| Zip7Sym7 (a6989586621679965937 :: [a]) (a6989586621679965938 :: [b]) (a6989586621679965939 :: [c]) (a6989586621679965940 :: [d]) (a6989586621679965941 :: [e]) (a6989586621679965942 :: [f]) (a6989586621679965943 :: [g]) = Zip7 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 a6989586621679965943 |
data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c]))) Source #
Instances
| SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
| SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWithSym1 (a6989586621679815347 :: a ~> (b ~> c)) (b1 :: TyFun [a] ([b] ~> [c])) Source #
Instances
| SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWithSym1 d) # | |
| SuppressUnusedWarnings (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) = ZipWithSym2 a6989586621679815347 a6989586621679815348 | |
data ZipWithSym2 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (c1 :: TyFun [b] [c]) Source #
Instances
| SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithSym2 d x) # | |
| SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> [a] -> TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWithSym2 d1 d2) # | |
| SuppressUnusedWarnings (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) = ZipWith a6989586621679815347 a6989586621679815348 a6989586621679815349 | |
type family ZipWithSym3 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (a6989586621679815349 :: [b]) :: [c] where ... Source #
Equations
| ZipWithSym3 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (a6989586621679815349 :: [b]) = ZipWith a6989586621679815347 a6989586621679815348 a6989586621679815349 |
data ZipWith3Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d])))) Source #
Instances
| SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
| SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679815332 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWith3Sym1 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (b1 :: TyFun [a] ([b] ~> ([c] ~> [d]))) Source #
Instances
| SingI1 (ZipWith3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym1 d2) # | |
| SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) = ZipWith3Sym2 a6989586621679815332 a6989586621679815333 | |
data ZipWith3Sym2 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (c1 :: TyFun [b] ([c] ~> [d])) Source #
Instances
| SingI d2 => SingI1 (ZipWith3Sym2 d2 :: [a] -> TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWith3Sym2 d2 x) # | |
| SingI2 (ZipWith3Sym2 :: (a ~> (b ~> (c ~> d))) -> [a] -> TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym2 d2 d3) # | |
| SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) = ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 | |
data ZipWith3Sym3 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [b]) (d1 :: TyFun [c] [d]) Source #
Instances
| SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d2, SingI d3) => SingI1 (ZipWith3Sym3 d2 d3 :: [b] -> TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [b]). Sing x -> Sing (ZipWith3Sym3 d2 d3 x) # | |
| (SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (ZipWith3Sym3 d2 d3 d4) # | |
| SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) = ZipWith3 a6989586621679815332 a6989586621679815333 a6989586621679815334 a6989586621679815335 | |
type family ZipWith3Sym4 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [b]) (a6989586621679815335 :: [c]) :: [d] where ... Source #
Equations
| ZipWith3Sym4 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [b]) (a6989586621679815335 :: [c]) = ZipWith3 a6989586621679815332 a6989586621679815333 a6989586621679815334 a6989586621679815335 |
data ZipWith4Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
data ZipWith4Sym1 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) = ZipWith4Sym2 a6989586621679965901 a6989586621679965902 | |
data ZipWith4Sym2 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> [e]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) = ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 | |
data ZipWith4Sym3 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (d1 :: TyFun [c] ([d] ~> [e])) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) = ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 | |
data ZipWith4Sym4 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (a6989586621679965904 :: [c]) (e1 :: TyFun [d] [e]) Source #
Instances
| SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) (a6989586621679965905 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) (a6989586621679965905 :: [d]) = ZipWith4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 a6989586621679965905 | |
type family ZipWith4Sym5 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (a6989586621679965904 :: [c]) (a6989586621679965905 :: [d]) :: [e] where ... Source #
Equations
| ZipWith4Sym5 (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679965902 :: [a]) (a6989586621679965903 :: [b]) (a6989586621679965904 :: [c]) (a6989586621679965905 :: [d]) = ZipWith4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 a6989586621679965905 |
data ZipWith5Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
data ZipWith5Sym1 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) = ZipWith5Sym2 a6989586621679965878 a6989586621679965879 | |
data ZipWith5Sym2 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) = ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 | |
data ZipWith5Sym3 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> [f]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) = ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 | |
data ZipWith5Sym4 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (e1 :: TyFun [d] ([e] ~> [f])) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) = ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 | |
data ZipWith5Sym5 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (a6989586621679965882 :: [d]) (f1 :: TyFun [e] [f]) Source #
Instances
| SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) (a6989586621679965883 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) (a6989586621679965883 :: [e]) = ZipWith5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 a6989586621679965883 | |
type family ZipWith5Sym6 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (a6989586621679965882 :: [d]) (a6989586621679965883 :: [e]) :: [f] where ... Source #
Equations
| ZipWith5Sym6 (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679965879 :: [a]) (a6989586621679965880 :: [b]) (a6989586621679965881 :: [c]) (a6989586621679965882 :: [d]) (a6989586621679965883 :: [e]) = ZipWith5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 a6989586621679965883 |
data ZipWith6Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
data ZipWith6Sym1 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) = ZipWith6Sym2 a6989586621679965851 a6989586621679965852 | |
data ZipWith6Sym2 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) = ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 | |
data ZipWith6Sym3 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) = ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 | |
data ZipWith6Sym4 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> [g]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) = ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 | |
data ZipWith6Sym5 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (f1 :: TyFun [e] ([f] ~> [g])) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) = ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 | |
data ZipWith6Sym6 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (a6989586621679965856 :: [e]) (g1 :: TyFun [f] [g]) Source #
Instances
| SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) (a6989586621679965857 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) (a6989586621679965857 :: [f]) = ZipWith6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 a6989586621679965857 | |
type family ZipWith6Sym7 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (a6989586621679965856 :: [e]) (a6989586621679965857 :: [f]) :: [g] where ... Source #
Equations
| ZipWith6Sym7 (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679965852 :: [a]) (a6989586621679965853 :: [b]) (a6989586621679965854 :: [c]) (a6989586621679965855 :: [d]) (a6989586621679965856 :: [e]) (a6989586621679965857 :: [f]) = ZipWith6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 a6989586621679965857 |
data ZipWith7Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWith7Sym1 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679965821 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal | |
data ZipWith7Sym2 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) = ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 | |
data ZipWith7Sym3 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) = ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 | |
data ZipWith7Sym4 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h])))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) = ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 | |
data ZipWith7Sym5 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (f1 :: TyFun [e] ([f] ~> ([g] ~> [h]))) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) = ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 | |
data ZipWith7Sym6 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (g1 :: TyFun [f] ([g] ~> [h])) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) = ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 | |
data ZipWith7Sym7 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (a6989586621679965826 :: [f]) (h1 :: TyFun [g] [h]) Source #
Instances
| SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) (a6989586621679965827 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) (a6989586621679965827 :: [g]) = ZipWith7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 a6989586621679965827 | |
type family ZipWith7Sym8 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (a6989586621679965826 :: [f]) (a6989586621679965827 :: [g]) :: [h] where ... Source #
Equations
| ZipWith7Sym8 (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679965821 :: [a]) (a6989586621679965822 :: [b]) (a6989586621679965823 :: [c]) (a6989586621679965824 :: [d]) (a6989586621679965825 :: [e]) (a6989586621679965826 :: [f]) (a6989586621679965827 :: [g]) = ZipWith7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 a6989586621679965827 |
data UnzipSym0 (a1 :: TyFun [(a, b)] ([a], [b])) Source #
Instances
| SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
| SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679815313 :: [(a, b)]) Source # | |
data Unzip3Sym0 (a1 :: TyFun [(a, b, c)] ([a], [b], [c])) Source #
Instances
| SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679815295 :: [(a, b, c)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679815295 :: [(a, b, c)]) = Unzip3 a6989586621679815295 | |
type family Unzip3Sym1 (a6989586621679815295 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Equations
| Unzip3Sym1 (a6989586621679815295 :: [(a, b, c)]) = Unzip3 a6989586621679815295 |
data Unzip4Sym0 (a1 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d])) Source #
Instances
| SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679815275 :: [(a, b, c, d)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679815275 :: [(a, b, c, d)]) = Unzip4 a6989586621679815275 | |
type family Unzip4Sym1 (a6989586621679815275 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #
Equations
| Unzip4Sym1 (a6989586621679815275 :: [(a, b, c, d)]) = Unzip4 a6989586621679815275 |
data Unzip5Sym0 (a1 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e])) Source #
Instances
| SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679815253 :: [(a, b, c, d, e)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679815253 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679815253 | |
type family Unzip5Sym1 (a6989586621679815253 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #
Equations
| Unzip5Sym1 (a6989586621679815253 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679815253 |
data Unzip6Sym0 (a1 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f])) Source #
Instances
| SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679815229 :: [(a, b, c, d, e, f)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679815229 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679815229 | |
type family Unzip6Sym1 (a6989586621679815229 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #
Equations
| Unzip6Sym1 (a6989586621679815229 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679815229 |
data Unzip7Sym0 (a1 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g])) Source #
Instances
| SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679815203 | |
type family Unzip7Sym1 (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Equations
| Unzip7Sym1 (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679815203 |
data UnlinesSym0 (a :: TyFun [Symbol] Symbol) Source #
Instances
| SingI UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnlinesSym0 # | |
| SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply UnlinesSym0 (a6989586621679815198 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnlinesSym1 (a6989586621679815198 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnlinesSym1 a6989586621679815198 = Unlines a6989586621679815198 |
data UnwordsSym0 (a :: TyFun [Symbol] Symbol) Source #
Instances
| SingI UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing UnwordsSym0 # | |
| SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply UnwordsSym0 (a6989586621679815188 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal | |
type family UnwordsSym1 (a6989586621679815188 :: [Symbol]) :: Symbol where ... Source #
Equations
| UnwordsSym1 a6989586621679815188 = Unwords a6989586621679815188 |
data DeleteSym0 (a1 :: TyFun a ([a] ~> [a])) Source #
Instances
| SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815182 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815182 :: a) = DeleteSym1 a6989586621679815182 | |
data DeleteSym1 (a6989586621679815182 :: a) (b :: TyFun [a] [a]) Source #
Instances
| SEq a => SingI1 (DeleteSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (DeleteSym1 x) # | |
| (SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteSym1 d) # | |
| SuppressUnusedWarnings (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) (a6989586621679815183 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) (a6989586621679815183 :: [a]) = Delete a6989586621679815182 a6989586621679815183 | |
type family DeleteSym2 (a6989586621679815182 :: a) (a6989586621679815183 :: [a]) :: [a] where ... Source #
Equations
| DeleteSym2 (a6989586621679815182 :: a) (a6989586621679815183 :: [a]) = Delete a6989586621679815182 a6989586621679815183 |
data (\\@#@$) (a1 :: TyFun [a] ([a] ~> [a])) infix 5 Source #
Instances
| SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815171 :: [a]) Source # | |
data (a6989586621679815171 :: [a]) \\@#@$$ (b :: TyFun [a] [a]) infix 5 Source #
Instances
| SEq a => SingI1 ((\\@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # | |
| (SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings ((\\@#@$$) a6989586621679815171 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply ((\\@#@$$) a6989586621679815171 :: TyFun [a] [a] -> Type) (a6989586621679815172 :: [a]) Source # | |
type family (a6989586621679815171 :: [a]) \\@#@$$$ (a6989586621679815172 :: [a]) :: [a] where ... infix 5 Source #
data UnionSym0 (a1 :: TyFun [a] ([a] ~> [a])) Source #
Instances
| SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814598 :: [a]) Source # | |
data UnionSym1 (a6989586621679814598 :: [a]) (b :: TyFun [a] [a]) Source #
Instances
| SEq a => SingI1 (UnionSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
| (SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (UnionSym1 a6989586621679814598 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionSym1 a6989586621679814598 :: TyFun [a] [a] -> Type) (a6989586621679814599 :: [a]) Source # | |
type family UnionSym2 (a6989586621679814598 :: [a]) (a6989586621679814599 :: [a]) :: [a] where ... Source #
data IntersectSym0 (a1 :: TyFun [a] ([a] ~> [a])) Source #
Instances
| SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814989 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814989 :: [a]) = IntersectSym1 a6989586621679814989 | |
data IntersectSym1 (a6989586621679814989 :: [a]) (b :: TyFun [a] [a]) Source #
Instances
| SEq a => SingI1 (IntersectSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectSym1 x) # | |
| (SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectSym1 d) # | |
| SuppressUnusedWarnings (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) (a6989586621679814990 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) (a6989586621679814990 :: [a]) = Intersect a6989586621679814989 a6989586621679814990 | |
type family IntersectSym2 (a6989586621679814989 :: [a]) (a6989586621679814990 :: [a]) :: [a] where ... Source #
Equations
| IntersectSym2 (a6989586621679814989 :: [a]) (a6989586621679814990 :: [a]) = Intersect a6989586621679814989 a6989586621679814990 |
data InsertSym0 (a1 :: TyFun a ([a] ~> [a])) Source #
Instances
| SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679814791 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679814791 :: a) = InsertSym1 a6989586621679814791 | |
data InsertSym1 (a6989586621679814791 :: a) (b :: TyFun [a] [a]) Source #
Instances
| SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) # | |
| (SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertSym1 d) # | |
| SuppressUnusedWarnings (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) (a6989586621679814792 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) (a6989586621679814792 :: [a]) = Insert a6989586621679814791 a6989586621679814792 | |
type family InsertSym2 (a6989586621679814791 :: a) (a6989586621679814792 :: [a]) :: [a] where ... Source #
Equations
| InsertSym2 (a6989586621679814791 :: a) (a6989586621679814792 :: [a]) = Insert a6989586621679814791 a6989586621679814792 |
data SortSym0 (a1 :: TyFun [a] [a]) Source #
Instances
data NubBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a])) Source #
Instances
| SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679814626 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621679814626 :: a ~> (a ~> Bool)) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (NubBySym1 a6989586621679814626 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # | |
| type Apply (NubBySym1 a6989586621679814626 :: TyFun [a] [a] -> Type) (a6989586621679814627 :: [a]) Source # | |
type family NubBySym2 (a6989586621679814626 :: a ~> (a ~> Bool)) (a6989586621679814627 :: [a]) :: [a] where ... Source #
data DeleteBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a]))) Source #
Instances
| SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
| SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815152 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal | |
data DeleteBySym1 (a6989586621679815152 :: a ~> (a ~> Bool)) (b :: TyFun a ([a] ~> [a])) Source #
Instances
| SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteBySym1 d) # | |
| SuppressUnusedWarnings (DeleteBySym1 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DeleteBySym1 :: (a ~> (a ~> Bool)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (DeleteBySym1 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815153 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym1 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815153 :: a) = DeleteBySym2 a6989586621679815152 a6989586621679815153 | |
data DeleteBySym2 (a6989586621679815152 :: a ~> (a ~> Bool)) (a6989586621679815153 :: a) (c :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI1 (DeleteBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (DeleteBySym2 d x) # | |
| SingI2 (DeleteBySym2 :: (a ~> (a ~> Bool)) -> a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteBySym2 d1 d2) # | |
| SuppressUnusedWarnings (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) (a6989586621679815154 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) (a6989586621679815154 :: [a]) = DeleteBy a6989586621679815152 a6989586621679815153 a6989586621679815154 | |
type family DeleteBySym3 (a6989586621679815152 :: a ~> (a ~> Bool)) (a6989586621679815153 :: a) (a6989586621679815154 :: [a]) :: [a] where ... Source #
Equations
| DeleteBySym3 (a6989586621679815152 :: a ~> (a ~> Bool)) (a6989586621679815153 :: a) (a6989586621679815154 :: [a]) = DeleteBy a6989586621679815152 a6989586621679815153 a6989586621679815154 |
data DeleteFirstsBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a]))) Source #
Instances
| SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
| SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679815142 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal | |
data DeleteFirstsBySym1 (a6989586621679815142 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a])) Source #
Instances
| SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteFirstsBySym1 d) # | |
| SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (DeleteFirstsBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) = DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 | |
data DeleteFirstsBySym2 (a6989586621679815142 :: a ~> (a ~> Bool)) (a6989586621679815143 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI1 (DeleteFirstsBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (DeleteFirstsBySym2 d x) # | |
| SingI2 (DeleteFirstsBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (DeleteFirstsBySym2 d1 d2) # | |
| SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) (a6989586621679815144 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) (a6989586621679815144 :: [a]) = DeleteFirstsBy a6989586621679815142 a6989586621679815143 a6989586621679815144 | |
type family DeleteFirstsBySym3 (a6989586621679815142 :: a ~> (a ~> Bool)) (a6989586621679815143 :: [a]) (a6989586621679815144 :: [a]) :: [a] where ... Source #
Equations
| DeleteFirstsBySym3 (a6989586621679815142 :: a ~> (a ~> Bool)) (a6989586621679815143 :: [a]) (a6989586621679815144 :: [a]) = DeleteFirstsBy a6989586621679815142 a6989586621679815143 a6989586621679815144 |
data UnionBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a]))) Source #
Instances
| SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
| SuppressUnusedWarnings (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814606 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal | |
data UnionBySym1 (a6989586621679814606 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a])) Source #
Instances
| SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnionBySym1 d) # | |
| SuppressUnusedWarnings (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (UnionBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) = UnionBySym2 a6989586621679814606 a6989586621679814607 | |
data UnionBySym2 (a6989586621679814606 :: a ~> (a ~> Bool)) (a6989586621679814607 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI1 (UnionBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (UnionBySym2 d x) # | |
| SingI2 (UnionBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (UnionBySym2 d1 d2) # | |
| SuppressUnusedWarnings (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) (a6989586621679814608 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) (a6989586621679814608 :: [a]) = UnionBy a6989586621679814606 a6989586621679814607 a6989586621679814608 | |
type family UnionBySym3 (a6989586621679814606 :: a ~> (a ~> Bool)) (a6989586621679814607 :: [a]) (a6989586621679814608 :: [a]) :: [a] where ... Source #
Equations
| UnionBySym3 (a6989586621679814606 :: a ~> (a ~> Bool)) (a6989586621679814607 :: [a]) (a6989586621679814608 :: [a]) = UnionBy a6989586621679814606 a6989586621679814607 a6989586621679814608 |
data IntersectBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a]))) Source #
Instances
| SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
| SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814967 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal | |
data IntersectBySym1 (a6989586621679814967 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a])) Source #
Instances
| SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectBySym1 d) # | |
| SuppressUnusedWarnings (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (IntersectBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) = IntersectBySym2 a6989586621679814967 a6989586621679814968 | |
data IntersectBySym2 (a6989586621679814967 :: a ~> (a ~> Bool)) (a6989586621679814968 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI1 (IntersectBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectBySym2 d x) # | |
| SingI2 (IntersectBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (IntersectBySym2 d1 d2) # | |
| SuppressUnusedWarnings (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) (a6989586621679814969 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) (a6989586621679814969 :: [a]) = IntersectBy a6989586621679814967 a6989586621679814968 a6989586621679814969 | |
type family IntersectBySym3 (a6989586621679814967 :: a ~> (a ~> Bool)) (a6989586621679814968 :: [a]) (a6989586621679814969 :: [a]) :: [a] where ... Source #
Equations
| IntersectBySym3 (a6989586621679814967 :: a ~> (a ~> Bool)) (a6989586621679814968 :: [a]) (a6989586621679814969 :: [a]) = IntersectBy a6989586621679814967 a6989586621679814968 a6989586621679814969 |
data GroupBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]])) Source #
Instances
| SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
| SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679814759 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal | |
data GroupBySym1 (a6989586621679814759 :: a ~> (a ~> Bool)) (b :: TyFun [a] [[a]]) Source #
Instances
| SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (GroupBySym1 d) # | |
| SuppressUnusedWarnings (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) (a6989586621679814760 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) (a6989586621679814760 :: [a]) = GroupBy a6989586621679814759 a6989586621679814760 | |
type family GroupBySym2 (a6989586621679814759 :: a ~> (a ~> Bool)) (a6989586621679814760 :: [a]) :: [[a]] where ... Source #
Equations
| GroupBySym2 (a6989586621679814759 :: a ~> (a ~> Bool)) (a6989586621679814760 :: [a]) = GroupBy a6989586621679814759 a6989586621679814760 |
data SortBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a])) Source #
Instances
| SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
| SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679815130 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal | |
data SortBySym1 (a6989586621679815130 :: a ~> (a ~> Ordering)) (b :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (SortBySym1 d) # | |
| SuppressUnusedWarnings (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) (a6989586621679815131 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) (a6989586621679815131 :: [a]) = SortBy a6989586621679815130 a6989586621679815131 | |
type family SortBySym2 (a6989586621679815130 :: a ~> (a ~> Ordering)) (a6989586621679815131 :: [a]) :: [a] where ... Source #
Equations
| SortBySym2 (a6989586621679815130 :: a ~> (a ~> Ordering)) (a6989586621679815131 :: [a]) = SortBy a6989586621679815130 a6989586621679815131 |
data InsertBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a]))) Source #
Instances
| SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
| SuppressUnusedWarnings (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815110 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal | |
data InsertBySym1 (a6989586621679815110 :: a ~> (a ~> Ordering)) (b :: TyFun a ([a] ~> [a])) Source #
Instances
| SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertBySym1 d) # | |
| SuppressUnusedWarnings (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| SingI1 (InsertBySym1 :: (a ~> (a ~> Ordering)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) = InsertBySym2 a6989586621679815110 a6989586621679815111 | |
data InsertBySym2 (a6989586621679815110 :: a ~> (a ~> Ordering)) (a6989586621679815111 :: a) (c :: TyFun [a] [a]) Source #
Instances
| SingI d => SingI1 (InsertBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods liftSing :: forall (x :: a). Sing x -> Sing (InsertBySym2 d x) # | |
| SingI2 (InsertBySym2 :: (a ~> (a ~> Ordering)) -> a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| (SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods sing :: Sing (InsertBySym2 d1 d2) # | |
| SuppressUnusedWarnings (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) (a6989586621679815112 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) (a6989586621679815112 :: [a]) = InsertBy a6989586621679815110 a6989586621679815111 a6989586621679815112 | |
type family InsertBySym3 (a6989586621679815110 :: a ~> (a ~> Ordering)) (a6989586621679815111 :: a) (a6989586621679815112 :: [a]) :: [a] where ... Source #
Equations
| InsertBySym3 (a6989586621679815110 :: a ~> (a ~> Ordering)) (a6989586621679815111 :: a) (a6989586621679815112 :: [a]) = InsertBy a6989586621679815110 a6989586621679815111 a6989586621679815112 |
data MaximumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a)) Source #
Instances
| SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
| SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390215 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons | |
data MaximumBySym1 (a6989586621680390215 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a) Source #
Instances
| SFoldable t => SingI1 (MaximumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (MaximumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) (a6989586621680390216 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) (a6989586621680390216 :: t a) = MaximumBy a6989586621680390215 a6989586621680390216 | |
type family MaximumBySym2 (a6989586621680390215 :: a ~> (a ~> Ordering)) (a6989586621680390216 :: t a) :: a where ... Source #
Equations
| MaximumBySym2 (a6989586621680390215 :: a ~> (a ~> Ordering)) (a6989586621680390216 :: t a) = MaximumBy a6989586621680390215 a6989586621680390216 |
data MinimumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a)) Source #
Instances
| SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
| SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390195 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons | |
data MinimumBySym1 (a6989586621680390195 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a) Source #
Instances
| SFoldable t => SingI1 (MinimumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # | |
| (SFoldable t, SingI d) => SingI (MinimumBySym1 d :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons | |
| SuppressUnusedWarnings (MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type) (a6989586621680390196 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type) (a6989586621680390196 :: t a) = MinimumBy a6989586621680390195 a6989586621680390196 | |
type family MinimumBySym2 (a6989586621680390195 :: a ~> (a ~> Ordering)) (a6989586621680390196 :: t a) :: a where ... Source #
Equations
| MinimumBySym2 (a6989586621680390195 :: a ~> (a ~> Ordering)) (a6989586621680390196 :: t a) = MinimumBy a6989586621680390195 a6989586621680390196 |
data GenericLengthSym0 (a1 :: TyFun [a] i) Source #
Instances
| SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
| SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a] i -> Type) Source # | |
Defined in Data.List.Singletons.Internal Methods suppressUnusedWarnings :: () # | |
| type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679814589 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679814589 :: [a]) = GenericLength a6989586621679814589 :: k2 | |
type family GenericLengthSym1 (a6989586621679814589 :: [a]) :: i where ... Source #
Equations
| GenericLengthSym1 (a6989586621679814589 :: [a]) = GenericLength a6989586621679814589 :: i |