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 |
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 (a6989586621679047148 :: a) :@#@$$ (b :: TyFun [a] [a])
- type family (a6989586621679047148 :: a) :@#@$$$ (a6989586621679047149 :: [a]) :: [a] where ...
- type family (a6989586621679181814 :: [a]) ++@#@$$$ (a6989586621679181815 :: [a]) :: [a] where ...
- data (a6989586621679181814 :: [a]) ++@#@$$ (b :: TyFun [a] [a])
- data (++@#@$) (a1 :: TyFun [a] ([a] ~> [a]))
- data HeadSym0 (a1 :: TyFun [a] a)
- type family HeadSym1 (a6989586621679825084 :: [a]) :: a where ...
- data LastSym0 (a1 :: TyFun [a] a)
- type family LastSym1 (a6989586621679825078 :: [a]) :: a where ...
- data TailSym0 (a1 :: TyFun [a] [a])
- type family TailSym1 (a6989586621679825074 :: [a]) :: [a] where ...
- data InitSym0 (a1 :: TyFun [a] [a])
- type family InitSym1 (a6989586621679825062 :: [a]) :: [a] where ...
- data NullSym0 (a1 :: TyFun (t a) Bool)
- type family NullSym1 (a6989586621680404321 :: t a) :: Bool where ...
- data LengthSym0 (a1 :: TyFun (t a) Natural)
- type family LengthSym1 (a6989586621680404324 :: t a) :: Natural where ...
- data MapSym0 (a1 :: TyFun (a ~> b) ([a] ~> [b]))
- data MapSym1 (a6989586621679181823 :: a ~> b) (b1 :: TyFun [a] [b])
- type family MapSym2 (a6989586621679181823 :: a ~> b) (a6989586621679181824 :: [a]) :: [b] where ...
- data ReverseSym0 (a1 :: TyFun [a] [a])
- type family ReverseSym1 (a6989586621679825047 :: [a]) :: [a] where ...
- data IntersperseSym0 (a1 :: TyFun a ([a] ~> [a]))
- data IntersperseSym1 (a6989586621679825040 :: a) (b :: TyFun [a] [a])
- type family IntersperseSym2 (a6989586621679825040 :: a) (a6989586621679825041 :: [a]) :: [a] where ...
- data IntercalateSym0 (a1 :: TyFun [a] ([[a]] ~> [a]))
- data IntercalateSym1 (a6989586621679825033 :: [a]) (b :: TyFun [[a]] [a])
- type family IntercalateSym2 (a6989586621679825033 :: [a]) (a6989586621679825034 :: [[a]]) :: [a] where ...
- data TransposeSym0 (a1 :: TyFun [[a]] [[a]])
- type family TransposeSym1 (a6989586621679823934 :: [[a]]) :: [[a]] where ...
- data SubsequencesSym0 (a1 :: TyFun [a] [[a]])
- type family SubsequencesSym1 (a6989586621679825028 :: [a]) :: [[a]] where ...
- data PermutationsSym0 (a1 :: TyFun [a] [[a]])
- type family PermutationsSym1 (a6989586621679824954 :: [a]) :: [[a]] where ...
- data FoldlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)))
- data FoldlSym1 (a6989586621680404296 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b))
- data FoldlSym2 (a6989586621680404296 :: b ~> (a ~> b)) (a6989586621680404297 :: b) (c :: TyFun (t a) b)
- type family FoldlSym3 (a6989586621680404296 :: b ~> (a ~> b)) (a6989586621680404297 :: b) (a6989586621680404298 :: t a) :: b where ...
- data Foldl'Sym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)))
- data Foldl'Sym1 (a6989586621680404303 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b))
- data Foldl'Sym2 (a6989586621680404303 :: b ~> (a ~> b)) (a6989586621680404304 :: b) (c :: TyFun (t a) b)
- type family Foldl'Sym3 (a6989586621680404303 :: b ~> (a ~> b)) (a6989586621680404304 :: b) (a6989586621680404305 :: t a) :: b where ...
- data Foldl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a))
- data Foldl1Sym1 (a6989586621680404314 :: a ~> (a ~> a)) (b :: TyFun (t a) a)
- type family Foldl1Sym2 (a6989586621680404314 :: a ~> (a ~> a)) (a6989586621680404315 :: t a) :: a where ...
- data Foldl1'Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> a))
- data Foldl1'Sym1 (a6989586621679824919 :: a ~> (a ~> a)) (b :: TyFun [a] a)
- type family Foldl1'Sym2 (a6989586621679824919 :: a ~> (a ~> a)) (a6989586621679824920 :: [a]) :: a where ...
- data FoldrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)))
- data FoldrSym1 (a6989586621680404282 :: a ~> (b ~> b)) (b1 :: TyFun b (t a ~> b))
- data FoldrSym2 (a6989586621680404282 :: a ~> (b ~> b)) (a6989586621680404283 :: b) (c :: TyFun (t a) b)
- type family FoldrSym3 (a6989586621680404282 :: a ~> (b ~> b)) (a6989586621680404283 :: b) (a6989586621680404284 :: t a) :: b where ...
- data Foldr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a))
- data Foldr1Sym1 (a6989586621680404309 :: a ~> (a ~> a)) (b :: TyFun (t a) a)
- type family Foldr1Sym2 (a6989586621680404309 :: a ~> (a ~> a)) (a6989586621680404310 :: t a) :: a where ...
- data ConcatSym0 (a1 :: TyFun (t [a]) [a])
- type family ConcatSym1 (a6989586621680404163 :: t [a]) :: [a] where ...
- data ConcatMapSym0 (a1 :: TyFun (a ~> [b]) (t a ~> [b]))
- data ConcatMapSym1 (a6989586621680404152 :: a ~> [b]) (b1 :: TyFun (t a) [b])
- type family ConcatMapSym2 (a6989586621680404152 :: a ~> [b]) (a6989586621680404153 :: t a) :: [b] where ...
- data AndSym0 (a :: TyFun (t Bool) Bool)
- type family AndSym1 (a6989586621680404147 :: t Bool) :: Bool where ...
- data OrSym0 (a :: TyFun (t Bool) Bool)
- type family OrSym1 (a6989586621680404141 :: t Bool) :: Bool where ...
- data AnySym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool))
- data AnySym1 (a6989586621680404133 :: a ~> Bool) (b :: TyFun (t a) Bool)
- type family AnySym2 (a6989586621680404133 :: a ~> Bool) (a6989586621680404134 :: t a) :: Bool where ...
- data AllSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool))
- data AllSym1 (a6989586621680404124 :: a ~> Bool) (b :: TyFun (t a) Bool)
- type family AllSym2 (a6989586621680404124 :: a ~> Bool) (a6989586621680404125 :: t a) :: Bool where ...
- data SumSym0 (a1 :: TyFun (t a) a)
- type family SumSym1 (a6989586621680404338 :: t a) :: a where ...
- data ProductSym0 (a1 :: TyFun (t a) a)
- type family ProductSym1 (a6989586621680404341 :: t a) :: a where ...
- data MaximumSym0 (a1 :: TyFun (t a) a)
- type family MaximumSym1 (a6989586621680404332 :: t a) :: a where ...
- data MinimumSym0 (a1 :: TyFun (t a) a)
- type family MinimumSym1 (a6989586621680404335 :: t a) :: a where ...
- data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])))
- data ScanlSym1 (a6989586621679824852 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> [b]))
- data ScanlSym2 (a6989586621679824852 :: b ~> (a ~> b)) (a6989586621679824853 :: b) (c :: TyFun [a] [b])
- type family ScanlSym3 (a6989586621679824852 :: b ~> (a ~> b)) (a6989586621679824853 :: b) (a6989586621679824854 :: [a]) :: [b] where ...
- data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]))
- data Scanl1Sym1 (a6989586621679824843 :: a ~> (a ~> a)) (b :: TyFun [a] [a])
- type family Scanl1Sym2 (a6989586621679824843 :: a ~> (a ~> a)) (a6989586621679824844 :: [a]) :: [a] where ...
- data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])))
- data ScanrSym1 (a6989586621679824825 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> [b]))
- data ScanrSym2 (a6989586621679824825 :: a ~> (b ~> b)) (a6989586621679824826 :: b) (c :: TyFun [a] [b])
- type family ScanrSym3 (a6989586621679824825 :: a ~> (b ~> b)) (a6989586621679824826 :: b) (a6989586621679824827 :: [a]) :: [b] where ...
- data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]))
- data Scanr1Sym1 (a6989586621679824805 :: a ~> (a ~> a)) (b :: TyFun [a] [a])
- type family Scanr1Sym2 (a6989586621679824805 :: a ~> (a ~> a)) (a6989586621679824806 :: [a]) :: [a] where ...
- data MapAccumLSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumLSym1 (a6989586621680756735 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumLSym2 (a6989586621680756735 :: a ~> (b ~> (a, c))) (a6989586621680756736 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumLSym3 (a6989586621680756735 :: a ~> (b ~> (a, c))) (a6989586621680756736 :: a) (a6989586621680756737 :: t b) :: (a, t c) where ...
- data MapAccumRSym0 (a1 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))))
- data MapAccumRSym1 (a6989586621680756725 :: a ~> (b ~> (a, c))) (b1 :: TyFun a (t b ~> (a, t c)))
- data MapAccumRSym2 (a6989586621680756725 :: a ~> (b ~> (a, c))) (a6989586621680756726 :: a) (c1 :: TyFun (t b) (a, t c))
- type family MapAccumRSym3 (a6989586621680756725 :: a ~> (b ~> (a, c))) (a6989586621680756726 :: a) (a6989586621680756727 :: t b) :: (a, t c) where ...
- data ReplicateSym0 (a1 :: TyFun Natural (a ~> [a]))
- data ReplicateSym1 (a6989586621679823942 :: Natural) (b :: TyFun a [a])
- type family ReplicateSym2 (a6989586621679823942 :: Natural) (a6989586621679823943 :: a) :: [a] where ...
- data UnfoldrSym0 (a1 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]))
- data UnfoldrSym1 (a6989586621679824697 :: b ~> Maybe (a, b)) (b1 :: TyFun b [a])
- type family UnfoldrSym2 (a6989586621679824697 :: b ~> Maybe (a, b)) (a6989586621679824698 :: b) :: [a] where ...
- data TakeSym0 (a1 :: TyFun Natural ([a] ~> [a]))
- data TakeSym1 (a6989586621679824097 :: Natural) (b :: TyFun [a] [a])
- type family TakeSym2 (a6989586621679824097 :: Natural) (a6989586621679824098 :: [a]) :: [a] where ...
- data DropSym0 (a1 :: TyFun Natural ([a] ~> [a]))
- data DropSym1 (a6989586621679824084 :: Natural) (b :: TyFun [a] [a])
- type family DropSym2 (a6989586621679824084 :: Natural) (a6989586621679824085 :: [a]) :: [a] where ...
- data SplitAtSym0 (a1 :: TyFun Natural ([a] ~> ([a], [a])))
- data SplitAtSym1 (a6989586621679824077 :: Natural) (b :: TyFun [a] ([a], [a]))
- type family SplitAtSym2 (a6989586621679824077 :: Natural) (a6989586621679824078 :: [a]) :: ([a], [a]) where ...
- data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data TakeWhileSym1 (a6989586621679824214 :: a ~> Bool) (b :: TyFun [a] [a])
- type family TakeWhileSym2 (a6989586621679824214 :: a ~> Bool) (a6989586621679824215 :: [a]) :: [a] where ...
- data DropWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data DropWhileSym1 (a6989586621679824199 :: a ~> Bool) (b :: TyFun [a] [a])
- type family DropWhileSym2 (a6989586621679824199 :: a ~> Bool) (a6989586621679824200 :: [a]) :: [a] where ...
- data DropWhileEndSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data DropWhileEndSym1 (a6989586621679824182 :: a ~> Bool) (b :: TyFun [a] [a])
- type family DropWhileEndSym2 (a6989586621679824182 :: a ~> Bool) (a6989586621679824183 :: [a]) :: [a] where ...
- data SpanSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data SpanSym1 (a6989586621679824145 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family SpanSym2 (a6989586621679824145 :: a ~> Bool) (a6989586621679824146 :: [a]) :: ([a], [a]) where ...
- data BreakSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data BreakSym1 (a6989586621679824110 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family BreakSym2 (a6989586621679824110 :: a ~> Bool) (a6989586621679824111 :: [a]) :: ([a], [a]) where ...
- data StripPrefixSym0 (a1 :: TyFun [a] ([a] ~> Maybe [a]))
- data StripPrefixSym1 (a6989586621679975077 :: [a]) (b :: TyFun [a] (Maybe [a]))
- type family StripPrefixSym2 (a6989586621679975077 :: [a]) (a6989586621679975078 :: [a]) :: Maybe [a] where ...
- data GroupSym0 (a1 :: TyFun [a] [[a]])
- type family GroupSym1 (a6989586621679824072 :: [a]) :: [[a]] where ...
- data InitsSym0 (a1 :: TyFun [a] [[a]])
- type family InitsSym1 (a6989586621679824687 :: [a]) :: [[a]] where ...
- data TailsSym0 (a1 :: TyFun [a] [[a]])
- type family TailsSym1 (a6989586621679824679 :: [a]) :: [[a]] where ...
- data IsPrefixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsPrefixOfSym1 (a6989586621679824671 :: [a]) (b :: TyFun [a] Bool)
- type family IsPrefixOfSym2 (a6989586621679824671 :: [a]) (a6989586621679824672 :: [a]) :: Bool where ...
- data IsSuffixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsSuffixOfSym1 (a6989586621679824664 :: [a]) (b :: TyFun [a] Bool)
- type family IsSuffixOfSym2 (a6989586621679824664 :: [a]) (a6989586621679824665 :: [a]) :: Bool where ...
- data IsInfixOfSym0 (a1 :: TyFun [a] ([a] ~> Bool))
- data IsInfixOfSym1 (a6989586621679824657 :: [a]) (b :: TyFun [a] Bool)
- type family IsInfixOfSym2 (a6989586621679824657 :: [a]) (a6989586621679824658 :: [a]) :: Bool where ...
- data ElemSym0 (a1 :: TyFun a (t a ~> Bool))
- data ElemSym1 (a6989586621680404328 :: a) (b :: TyFun (t a) Bool)
- type family ElemSym2 (a6989586621680404328 :: a) (a6989586621680404329 :: t a) :: Bool where ...
- data NotElemSym0 (a1 :: TyFun a (t a ~> Bool))
- data NotElemSym1 (a6989586621680404075 :: a) (b :: TyFun (t a) Bool)
- type family NotElemSym2 (a6989586621680404075 :: a) (a6989586621680404076 :: t a) :: Bool where ...
- data LookupSym0 (a1 :: TyFun a ([(a, b)] ~> Maybe b))
- data LookupSym1 (a6989586621679824005 :: a) (b1 :: TyFun [(a, b)] (Maybe b))
- type family LookupSym2 (a6989586621679824005 :: a) (a6989586621679824006 :: [(a, b)]) :: Maybe b where ...
- data FindSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Maybe a))
- data FindSym1 (a6989586621680404057 :: a ~> Bool) (b :: TyFun (t a) (Maybe a))
- type family FindSym2 (a6989586621680404057 :: a ~> Bool) (a6989586621680404058 :: t a) :: Maybe a where ...
- data FilterSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a]))
- data FilterSym1 (a6989586621679824314 :: a ~> Bool) (b :: TyFun [a] [a])
- type family FilterSym2 (a6989586621679824314 :: a ~> Bool) (a6989586621679824315 :: [a]) :: [a] where ...
- data PartitionSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])))
- data PartitionSym1 (a6989586621679823998 :: a ~> Bool) (b :: TyFun [a] ([a], [a]))
- type family PartitionSym2 (a6989586621679823998 :: a ~> Bool) (a6989586621679823999 :: [a]) :: ([a], [a]) where ...
- data (!!@#@$) (a1 :: TyFun [a] (Natural ~> a))
- data (a6989586621679823922 :: [a]) !!@#@$$ (b :: TyFun Natural a)
- type family (a6989586621679823922 :: [a]) !!@#@$$$ (a6989586621679823923 :: Natural) :: a where ...
- data ElemIndexSym0 (a1 :: TyFun a ([a] ~> Maybe Natural))
- data ElemIndexSym1 (a6989586621679824298 :: a) (b :: TyFun [a] (Maybe Natural))
- type family ElemIndexSym2 (a6989586621679824298 :: a) (a6989586621679824299 :: [a]) :: Maybe Natural where ...
- data ElemIndicesSym0 (a1 :: TyFun a ([a] ~> [Natural]))
- data ElemIndicesSym1 (a6989586621679824289 :: a) (b :: TyFun [a] [Natural])
- type family ElemIndicesSym2 (a6989586621679824289 :: a) (a6989586621679824290 :: [a]) :: [Natural] where ...
- data FindIndexSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural))
- data FindIndexSym1 (a6989586621679824280 :: a ~> Bool) (b :: TyFun [a] (Maybe Natural))
- type family FindIndexSym2 (a6989586621679824280 :: a ~> Bool) (a6989586621679824281 :: [a]) :: Maybe Natural where ...
- data FindIndicesSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [Natural]))
- data FindIndicesSym1 (a6989586621679824257 :: a ~> Bool) (b :: TyFun [a] [Natural])
- type family FindIndicesSym2 (a6989586621679824257 :: a ~> Bool) (a6989586621679824258 :: [a]) :: [Natural] where ...
- data ZipSym0 (a1 :: TyFun [a] ([b] ~> [(a, b)]))
- data ZipSym1 (a6989586621679824632 :: [a]) (b1 :: TyFun [b] [(a, b)])
- type family ZipSym2 (a6989586621679824632 :: [a]) (a6989586621679824633 :: [b]) :: [(a, b)] where ...
- data Zip3Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])))
- data Zip3Sym1 (a6989586621679824620 :: [a]) (b1 :: TyFun [b] ([c] ~> [(a, b, c)]))
- data Zip3Sym2 (a6989586621679824620 :: [a]) (a6989586621679824621 :: [b]) (c1 :: TyFun [c] [(a, b, c)])
- type family Zip3Sym3 (a6989586621679824620 :: [a]) (a6989586621679824621 :: [b]) (a6989586621679824622 :: [c]) :: [(a, b, c)] where ...
- data Zip4Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))))
- data Zip4Sym1 (a6989586621679975066 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])))
- data Zip4Sym2 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (c1 :: TyFun [c] ([d] ~> [(a, b, c, d)]))
- data Zip4Sym3 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (a6989586621679975068 :: [c]) (d1 :: TyFun [d] [(a, b, c, d)])
- type family Zip4Sym4 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (a6989586621679975068 :: [c]) (a6989586621679975069 :: [d]) :: [(a, b, c, d)] where ...
- data Zip5Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))))
- data Zip5Sym1 (a6989586621679975043 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))))
- data Zip5Sym2 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])))
- data Zip5Sym3 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (d1 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]))
- data Zip5Sym4 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (a6989586621679975046 :: [d]) (e1 :: TyFun [e] [(a, b, c, d, e)])
- type family Zip5Sym5 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (a6989586621679975046 :: [d]) (a6989586621679975047 :: [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 (a6989586621679975015 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))))
- data Zip6Sym2 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))
- data Zip6Sym3 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))
- data Zip6Sym4 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (e1 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]))
- data Zip6Sym5 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (a6989586621679975019 :: [e]) (f1 :: TyFun [f] [(a, b, c, d, e, f)])
- type family Zip6Sym6 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (a6989586621679975019 :: [e]) (a6989586621679975020 :: [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 (a6989586621679974982 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))))
- data Zip7Sym2 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))
- data Zip7Sym3 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))
- data Zip7Sym4 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (e1 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))
- data Zip7Sym5 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (f1 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]))
- data Zip7Sym6 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (a6989586621679974987 :: [f]) (g1 :: TyFun [g] [(a, b, c, d, e, f, g)])
- type family Zip7Sym7 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (a6989586621679974987 :: [f]) (a6989586621679974988 :: [g]) :: [(a, b, c, d, e, f, g)] where ...
- data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])))
- data ZipWithSym1 (a6989586621679824608 :: a ~> (b ~> c)) (b1 :: TyFun [a] ([b] ~> [c]))
- data ZipWithSym2 (a6989586621679824608 :: a ~> (b ~> c)) (a6989586621679824609 :: [a]) (c1 :: TyFun [b] [c])
- type family ZipWithSym3 (a6989586621679824608 :: a ~> (b ~> c)) (a6989586621679824609 :: [a]) (a6989586621679824610 :: [b]) :: [c] where ...
- data ZipWith3Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))))
- data ZipWith3Sym1 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (b1 :: TyFun [a] ([b] ~> ([c] ~> [d])))
- data ZipWith3Sym2 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (c1 :: TyFun [b] ([c] ~> [d]))
- data ZipWith3Sym3 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (a6989586621679824595 :: [b]) (d1 :: TyFun [c] [d])
- type family ZipWith3Sym4 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (a6989586621679824595 :: [b]) (a6989586621679824596 :: [c]) :: [d] where ...
- data ZipWith4Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))))
- data ZipWith4Sym1 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))))
- data ZipWith4Sym2 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> [e])))
- data ZipWith4Sym3 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (d1 :: TyFun [c] ([d] ~> [e]))
- data ZipWith4Sym4 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (a6989586621679974949 :: [c]) (e1 :: TyFun [d] [e])
- type family ZipWith4Sym5 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (a6989586621679974949 :: [c]) (a6989586621679974950 :: [d]) :: [e] where ...
- data ZipWith5Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))))
- data ZipWith5Sym1 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))))
- data ZipWith5Sym2 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))))
- data ZipWith5Sym3 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> [f])))
- data ZipWith5Sym4 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (e1 :: TyFun [d] ([e] ~> [f]))
- data ZipWith5Sym5 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (a6989586621679974927 :: [d]) (f1 :: TyFun [e] [f])
- type family ZipWith5Sym6 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (a6989586621679974927 :: [d]) (a6989586621679974928 :: [e]) :: [f] where ...
- data ZipWith6Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))))
- data ZipWith6Sym1 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))))
- data ZipWith6Sym2 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))
- data ZipWith6Sym3 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))))
- data ZipWith6Sym4 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> [g])))
- data ZipWith6Sym5 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (f1 :: TyFun [e] ([f] ~> [g]))
- data ZipWith6Sym6 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (a6989586621679974901 :: [e]) (g1 :: TyFun [f] [g])
- type family ZipWith6Sym7 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (a6989586621679974901 :: [e]) (a6989586621679974902 :: [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 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))))
- data ZipWith7Sym2 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))
- data ZipWith7Sym3 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))
- data ZipWith7Sym4 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))))
- data ZipWith7Sym5 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (f1 :: TyFun [e] ([f] ~> ([g] ~> [h])))
- data ZipWith7Sym6 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (g1 :: TyFun [f] ([g] ~> [h]))
- data ZipWith7Sym7 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (a6989586621679974871 :: [f]) (h1 :: TyFun [g] [h])
- type family ZipWith7Sym8 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (a6989586621679974871 :: [f]) (a6989586621679974872 :: [g]) :: [h] where ...
- data UnzipSym0 (a1 :: TyFun [(a, b)] ([a], [b]))
- type family UnzipSym1 (a6989586621679824574 :: [(a, b)]) :: ([a], [b]) where ...
- data Unzip3Sym0 (a1 :: TyFun [(a, b, c)] ([a], [b], [c]))
- type family Unzip3Sym1 (a6989586621679824556 :: [(a, b, c)]) :: ([a], [b], [c]) where ...
- data Unzip4Sym0 (a1 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]))
- type family Unzip4Sym1 (a6989586621679824536 :: [(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 (a6989586621679824514 :: [(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 (a6989586621679824490 :: [(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 (a6989586621679824464 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ...
- data UnlinesSym0 (a :: TyFun [Symbol] Symbol)
- type family UnlinesSym1 (a6989586621679824459 :: [Symbol]) :: Symbol where ...
- data UnwordsSym0 (a :: TyFun [Symbol] Symbol)
- type family UnwordsSym1 (a6989586621679824449 :: [Symbol]) :: Symbol where ...
- data NubSym0 (a1 :: TyFun [a] [a])
- type family NubSym1 (a6989586621679823905 :: [a]) :: [a] where ...
- data DeleteSym0 (a1 :: TyFun a ([a] ~> [a]))
- data DeleteSym1 (a6989586621679824443 :: a) (b :: TyFun [a] [a])
- type family DeleteSym2 (a6989586621679824443 :: a) (a6989586621679824444 :: [a]) :: [a] where ...
- data (\\@#@$) (a1 :: TyFun [a] ([a] ~> [a]))
- data (a6989586621679824432 :: [a]) \\@#@$$ (b :: TyFun [a] [a])
- type family (a6989586621679824432 :: [a]) \\@#@$$$ (a6989586621679824433 :: [a]) :: [a] where ...
- data UnionSym0 (a1 :: TyFun [a] ([a] ~> [a]))
- data UnionSym1 (a6989586621679823859 :: [a]) (b :: TyFun [a] [a])
- type family UnionSym2 (a6989586621679823859 :: [a]) (a6989586621679823860 :: [a]) :: [a] where ...
- data IntersectSym0 (a1 :: TyFun [a] ([a] ~> [a]))
- data IntersectSym1 (a6989586621679824250 :: [a]) (b :: TyFun [a] [a])
- type family IntersectSym2 (a6989586621679824250 :: [a]) (a6989586621679824251 :: [a]) :: [a] where ...
- data InsertSym0 (a1 :: TyFun a ([a] ~> [a]))
- data InsertSym1 (a6989586621679824052 :: a) (b :: TyFun [a] [a])
- type family InsertSym2 (a6989586621679824052 :: a) (a6989586621679824053 :: [a]) :: [a] where ...
- data SortSym0 (a1 :: TyFun [a] [a])
- type family SortSym1 (a6989586621679824047 :: [a]) :: [a] where ...
- data NubBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]))
- data NubBySym1 (a6989586621679823887 :: a ~> (a ~> Bool)) (b :: TyFun [a] [a])
- type family NubBySym2 (a6989586621679823887 :: a ~> (a ~> Bool)) (a6989586621679823888 :: [a]) :: [a] where ...
- data DeleteBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])))
- data DeleteBySym1 (a6989586621679824413 :: a ~> (a ~> Bool)) (b :: TyFun a ([a] ~> [a]))
- data DeleteBySym2 (a6989586621679824413 :: a ~> (a ~> Bool)) (a6989586621679824414 :: a) (c :: TyFun [a] [a])
- type family DeleteBySym3 (a6989586621679824413 :: a ~> (a ~> Bool)) (a6989586621679824414 :: a) (a6989586621679824415 :: [a]) :: [a] where ...
- data DeleteFirstsBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data DeleteFirstsBySym1 (a6989586621679824403 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data DeleteFirstsBySym2 (a6989586621679824403 :: a ~> (a ~> Bool)) (a6989586621679824404 :: [a]) (c :: TyFun [a] [a])
- type family DeleteFirstsBySym3 (a6989586621679824403 :: a ~> (a ~> Bool)) (a6989586621679824404 :: [a]) (a6989586621679824405 :: [a]) :: [a] where ...
- data UnionBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data UnionBySym1 (a6989586621679823867 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data UnionBySym2 (a6989586621679823867 :: a ~> (a ~> Bool)) (a6989586621679823868 :: [a]) (c :: TyFun [a] [a])
- type family UnionBySym3 (a6989586621679823867 :: a ~> (a ~> Bool)) (a6989586621679823868 :: [a]) (a6989586621679823869 :: [a]) :: [a] where ...
- data IntersectBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])))
- data IntersectBySym1 (a6989586621679824228 :: a ~> (a ~> Bool)) (b :: TyFun [a] ([a] ~> [a]))
- data IntersectBySym2 (a6989586621679824228 :: a ~> (a ~> Bool)) (a6989586621679824229 :: [a]) (c :: TyFun [a] [a])
- type family IntersectBySym3 (a6989586621679824228 :: a ~> (a ~> Bool)) (a6989586621679824229 :: [a]) (a6989586621679824230 :: [a]) :: [a] where ...
- data GroupBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]))
- data GroupBySym1 (a6989586621679824020 :: a ~> (a ~> Bool)) (b :: TyFun [a] [[a]])
- type family GroupBySym2 (a6989586621679824020 :: a ~> (a ~> Bool)) (a6989586621679824021 :: [a]) :: [[a]] where ...
- data SortBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]))
- data SortBySym1 (a6989586621679824391 :: a ~> (a ~> Ordering)) (b :: TyFun [a] [a])
- type family SortBySym2 (a6989586621679824391 :: a ~> (a ~> Ordering)) (a6989586621679824392 :: [a]) :: [a] where ...
- data InsertBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])))
- data InsertBySym1 (a6989586621679824371 :: a ~> (a ~> Ordering)) (b :: TyFun a ([a] ~> [a]))
- data InsertBySym2 (a6989586621679824371 :: a ~> (a ~> Ordering)) (a6989586621679824372 :: a) (c :: TyFun [a] [a])
- type family InsertBySym3 (a6989586621679824371 :: a ~> (a ~> Ordering)) (a6989586621679824372 :: a) (a6989586621679824373 :: [a]) :: [a] where ...
- data MaximumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a))
- data MaximumBySym1 (a6989586621680404104 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a)
- type family MaximumBySym2 (a6989586621680404104 :: a ~> (a ~> Ordering)) (a6989586621680404105 :: t a) :: a where ...
- data MinimumBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a))
- data MinimumBySym1 (a6989586621680404084 :: a ~> (a ~> Ordering)) (b :: TyFun (t a) a)
- type family MinimumBySym2 (a6989586621680404084 :: a ~> (a ~> Ordering)) (a6989586621680404085 :: t a) :: a where ...
- data GenericLengthSym0 (a1 :: TyFun [a] i)
- type family GenericLengthSym1 (a6989586621679823850 :: [a]) :: i where ...
The singleton for lists
type family Sing :: k -> Type #
Instances
data SList (a1 :: [a]) where Source #
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 #
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 #
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 (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 :: 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 (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) 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 :: 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 (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 :: Either a2 a1) Source # | |
Defined in Data.Foldable.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' (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 :: 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' (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' (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 :: Either a2 a1) Source # | |
Defined in Data.Foldable.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 (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 :: 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 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 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 :: 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 :: [k2]) 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 :: Either a2 a1) Source # | |
Defined in Data.Foldable.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 :: 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 :: NonEmpty a1) Source # | |
Defined in Data.Foldable.Singletons | |
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 :: 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 :: 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 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.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 :: (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 (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 :: 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 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 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 :: 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 :: [k2]) 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 :: Either a2 a1) Source # | |
Defined in Data.Foldable.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 #
ConcatMap (f :: a1 ~> [a2]) (xs :: t a1) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a1 ~> ([a2] ~> [a2])) ([a2] ~> (t a1 ~> [a2])) -> Type) (Apply (Apply (Lambda_6989586621680404156Sym0 :: 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 #
Any (p :: a ~> Bool) (a_6989586621680404128 :: 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_6989586621680404128 |
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 #
All (p :: a ~> Bool) (a_6989586621680404119 :: 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_6989586621680404119 |
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 #
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 #
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_6989586621679820745 ': wild_6989586621679820747) :: [k]) = Case_6989586621679824816 f x wild_6989586621679820745 wild_6989586621679820747 (Let6989586621679824814Scrutinee_6989586621679820739Sym4 f x wild_6989586621679820745 wild_6989586621679820747) |
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 #
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 #
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 #
Replicate n (x :: k) = Case_6989586621679823948 n x (Let6989586621679823946Scrutinee_6989586621679820841Sym2 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 #
DropWhileEnd (p :: a ~> Bool) (a_6989586621679824177 :: [a]) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> ([a] ~> [a])) ([a] ~> ([a] ~> [a])) -> Type) (Apply (Apply (Lambda_6989586621679824186Sym0 :: TyFun (a ~> Bool) (TyFun [a] (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) p) a_6989586621679824177)) (NilSym0 :: [a])) a_6989586621679824177 |
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 #
Span (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679824147XsSym0 :: [a])) (Let6989586621679824147XsSym0 :: [a]) | |
Span (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679824156 p x xs' (Let6989586621679824154Scrutinee_6989586621679820821Sym3 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 #
Break (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679824112XsSym0 :: [a])) (Let6989586621679824112XsSym0 :: [a]) | |
Break (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679824121 p x xs' (Let6989586621679824119Scrutinee_6989586621679820823Sym3 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 #
StripPrefix ('[] :: [a]) (ys :: [a]) = Apply (JustSym0 :: TyFun [a] (Maybe [a]) -> Type) ys | |
StripPrefix (arg_6989586621679973768 :: [k]) (arg_6989586621679973770 :: [k]) = Case_6989586621679975082 arg_6989586621679973768 arg_6989586621679973770 (Apply (Apply (Tuple2Sym0 :: TyFun [k] ([k] ~> ([k], [k])) -> Type) arg_6989586621679973768) arg_6989586621679973770) |
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 #
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 #
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 (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 :: First a) Source # | |
Defined in Data.Foldable.Singletons | |
type Elem (arg1 :: a) (arg2 :: Last 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 (arg :: a1) (arg1 :: Arg a2 a1) Source # | |
Defined in Data.Semigroup.Singletons | |
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) Source # | |
Defined in Data.Foldable.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 #
Lookup (_key :: a) ('[] :: [(a, b)]) = NothingSym0 :: Maybe b | |
Lookup (key :: k1) ('(x, y) ': xys :: [(k1, k)]) = Case_6989586621679824014 key x y xys (Let6989586621679824012Scrutinee_6989586621679820837Sym4 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 #
Find (p :: a ~> Bool) (a_6989586621680404052 :: 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_6989586621680404061Sym0 :: TyFun (a ~> Bool) (TyFun (t a) (TyFun a (First a) -> Type) -> Type) -> Type) p) a_6989586621680404052))) a_6989586621680404052 |
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 #
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 #
FindIndex (p :: a ~> Bool) (a_6989586621679824275 :: [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_6989586621679824275 |
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 #
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_6989586621679824267Sym0 :: 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 (Let6989586621679824261BuildListSym2 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 #
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 #
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 #
Zip4 (a_6989586621679975053 :: [a]) (a_6989586621679975055 :: [b]) (a_6989586621679975057 :: [c]) (a_6989586621679975059 :: [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_6989586621679975053) a_6989586621679975055) a_6989586621679975057) a_6989586621679975059 |
type family Zip5 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) :: [(a, b, c, d, e)] where ... Source #
Zip5 (a_6989586621679975027 :: [a]) (a_6989586621679975029 :: [b]) (a_6989586621679975031 :: [c]) (a_6989586621679975033 :: [d]) (a_6989586621679975035 :: [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_6989586621679975027) a_6989586621679975029) a_6989586621679975031) a_6989586621679975033) a_6989586621679975035 |
type family Zip6 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) (a4 :: [d]) (a5 :: [e]) (a6 :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Zip6 (a_6989586621679974996 :: [a]) (a_6989586621679974998 :: [b]) (a_6989586621679975000 :: [c]) (a_6989586621679975002 :: [d]) (a_6989586621679975004 :: [e]) (a_6989586621679975006 :: [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_6989586621679974996) a_6989586621679974998) a_6989586621679975000) a_6989586621679975002) a_6989586621679975004) a_6989586621679975006 |
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 #
Zip7 (a_6989586621679974960 :: [a]) (a_6989586621679974962 :: [b]) (a_6989586621679974964 :: [c]) (a_6989586621679974966 :: [d]) (a_6989586621679974968 :: [e]) (a_6989586621679974970 :: [f]) (a_6989586621679974972 :: [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_6989586621679974960) a_6989586621679974962) a_6989586621679974964) a_6989586621679974966) a_6989586621679974968) a_6989586621679974970) a_6989586621679974972 |
type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: [a]) (a3 :: [b]) :: [c] where ... Source #
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 #
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 #
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 #
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 #
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 #
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 #
Unzip (xs :: [(k2, k3)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3) ~> (([k2], [k3]) ~> ([k2], [k3]))) (([k2], [k3]) ~> ([(k2, k3)] ~> ([k2], [k3]))) -> Type) (Apply (Lambda_6989586621679824576Sym0 :: 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 #
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_6989586621679824558Sym0 :: 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 #
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_6989586621679824538Sym0 :: 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 #
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_6989586621679824516Sym0 :: 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 #
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_6989586621679824492Sym0 :: 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 #
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_6989586621679824466Sym0 :: 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 Symbol
s
"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 #
(a_6989586621679824425 :: [a]) \\ (a_6989586621679824427 :: [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_6989586621679824425) a_6989586621679824427 |
(%\\) :: 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 #
DeleteFirstsBy (eq :: a ~> (a ~> Bool)) (a_6989586621679824395 :: [a]) (a_6989586621679824397 :: [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_6989586621679824395) a_6989586621679824397 |
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 #
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 #
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_6989586621679820807 ': wild_6989586621679820809 :: [b]) (wild_6989586621679820811 ': wild_6989586621679820813 :: [b]) = Apply (Apply ((>>=@#@$) :: TyFun [b] ((b ~> [b]) ~> [b]) -> Type) (Let6989586621679824236XsSym5 eq wild_6989586621679820807 wild_6989586621679820809 wild_6989586621679820811 wild_6989586621679820813)) (Apply (Apply (Apply (Apply (Apply (Lambda_6989586621679824239Sym0 :: TyFun (b ~> (b ~> Bool)) (TyFun b (TyFun [b] (TyFun b (TyFun [b] (TyFun b [b] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) eq) wild_6989586621679820807) wild_6989586621679820809) wild_6989586621679820811) wild_6989586621679820813) |
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 #
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) (Let6989586621679824025YsSym3 eq x xs))) (Apply (Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) eq) (Let6989586621679824025ZsSym3 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 #
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_6989586621679824383 cmp x y ys' (Let6989586621679824381Scrutinee_6989586621679820789Sym4 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 #
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
data (a6989586621679047148 :: 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 ((:@#@$$) a6989586621679047148 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.Singletons.Base.Instances suppressUnusedWarnings :: () # | |
type Apply ((:@#@$$) a6989586621679047148 :: TyFun [a] [a] -> Type) (a6989586621679047149 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances |
type family (a6989586621679047148 :: a) :@#@$$$ (a6989586621679047149 :: [a]) :: [a] where ... infixr 5 Source #
(a6989586621679047148 :: a) :@#@$$$ (a6989586621679047149 :: [a]) = a6989586621679047148 ': a6989586621679047149 |
type family (a6989586621679181814 :: [a]) ++@#@$$$ (a6989586621679181815 :: [a]) :: [a] where ... infixr 5 Source #
data (a6989586621679181814 :: [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 ((++@#@$$) a6989586621679181814 :: TyFun [a] [a] -> Type) Source # | |
Defined in GHC.Base.Singletons suppressUnusedWarnings :: () # | |
type Apply ((++@#@$$) a6989586621679181814 :: TyFun [a] [a] -> Type) (a6989586621679181815 :: [a]) Source # | |
data (++@#@$) (a1 :: TyFun [a] ([a] ~> [a])) infixr 5 Source #
Instances
data NullSym0 (a1 :: TyFun (t a) Bool) Source #
Instances
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 suppressUnusedWarnings :: () # | |
type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680404324 :: t a) Source # | |
Defined in Data.Foldable.Singletons |
type family LengthSym1 (a6989586621680404324 :: t a) :: Natural where ... Source #
LengthSym1 (a6989586621680404324 :: t a) = Length a6989586621680404324 |
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 suppressUnusedWarnings :: () # | |
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679181823 :: a ~> b) Source # | |
data MapSym1 (a6989586621679181823 :: 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 a6989586621679181823 :: TyFun [a] [b] -> Type) Source # | |
Defined in GHC.Base.Singletons suppressUnusedWarnings :: () # | |
type Apply (MapSym1 a6989586621679181823 :: TyFun [a] [b] -> Type) (a6989586621679181824 :: [a]) Source # | |
type family MapSym2 (a6989586621679181823 :: a ~> b) (a6989586621679181824 :: [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 suppressUnusedWarnings :: () # | |
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679825047 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679825047 :: [a]) = Reverse a6989586621679825047 |
type family ReverseSym1 (a6989586621679825047 :: [a]) :: [a] where ... Source #
ReverseSym1 (a6989586621679825047 :: [a]) = Reverse a6989586621679825047 |
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 suppressUnusedWarnings :: () # | |
type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679825040 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679825040 :: a) = IntersperseSym1 a6989586621679825040 |
data IntersperseSym1 (a6989586621679825040 :: a) (b :: TyFun [a] [a]) Source #
Instances
SingI1 (IntersperseSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IntersperseSym1 d) # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621679825040 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IntersperseSym1 a6989586621679825040 :: TyFun [a] [a] -> Type) (a6989586621679825041 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersperseSym1 a6989586621679825040 :: TyFun [a] [a] -> Type) (a6989586621679825041 :: [a]) = Intersperse a6989586621679825040 a6989586621679825041 |
type family IntersperseSym2 (a6989586621679825040 :: a) (a6989586621679825041 :: [a]) :: [a] where ... Source #
IntersperseSym2 (a6989586621679825040 :: a) (a6989586621679825041 :: [a]) = Intersperse a6989586621679825040 a6989586621679825041 |
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 suppressUnusedWarnings :: () # | |
type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679825033 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679825033 :: [a]) = IntercalateSym1 a6989586621679825033 |
data IntercalateSym1 (a6989586621679825033 :: [a]) (b :: TyFun [[a]] [a]) Source #
Instances
SingI1 (IntercalateSym1 :: [a] -> TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IntercalateSym1 d) # | |
SuppressUnusedWarnings (IntercalateSym1 a6989586621679825033 :: TyFun [[a]] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IntercalateSym1 a6989586621679825033 :: TyFun [[a]] [a] -> Type) (a6989586621679825034 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntercalateSym1 a6989586621679825033 :: TyFun [[a]] [a] -> Type) (a6989586621679825034 :: [[a]]) = Intercalate a6989586621679825033 a6989586621679825034 |
type family IntercalateSym2 (a6989586621679825033 :: [a]) (a6989586621679825034 :: [[a]]) :: [a] where ... Source #
IntercalateSym2 (a6989586621679825033 :: [a]) (a6989586621679825034 :: [[a]]) = Intercalate a6989586621679825033 a6989586621679825034 |
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 suppressUnusedWarnings :: () # | |
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679823934 :: [[a]]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679823934 :: [[a]]) = Transpose a6989586621679823934 |
type family TransposeSym1 (a6989586621679823934 :: [[a]]) :: [[a]] where ... Source #
TransposeSym1 (a6989586621679823934 :: [[a]]) = Transpose a6989586621679823934 |
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 suppressUnusedWarnings :: () # | |
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679825028 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679825028 :: [a]) = Subsequences a6989586621679825028 |
type family SubsequencesSym1 (a6989586621679825028 :: [a]) :: [[a]] where ... Source #
SubsequencesSym1 (a6989586621679825028 :: [a]) = Subsequences a6989586621679825028 |
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 suppressUnusedWarnings :: () # | |
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679824954 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679824954 :: [a]) = Permutations a6989586621679824954 |
type family PermutationsSym1 (a6989586621679824954 :: [a]) :: [[a]] where ... Source #
PermutationsSym1 (a6989586621679824954 :: [a]) = Permutations a6989586621679824954 |
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 suppressUnusedWarnings :: () # | |
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680404296 :: b ~> (a ~> b)) Source # | |
data FoldlSym1 (a6989586621680404296 :: 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 a6989586621680404296 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (FoldlSym1 a6989586621680404296 :: TyFun b (t a ~> b) -> Type) (a6989586621680404297 :: b) Source # | |
data FoldlSym2 (a6989586621680404296 :: b ~> (a ~> b)) (a6989586621680404297 :: 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 a6989586621680404296 a6989586621680404297 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (FoldlSym2 a6989586621680404296 a6989586621680404297 :: TyFun (t a) b -> Type) (a6989586621680404298 :: t a) Source # | |
type family FoldlSym3 (a6989586621680404296 :: b ~> (a ~> b)) (a6989586621680404297 :: b) (a6989586621680404298 :: 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 suppressUnusedWarnings :: () # | |
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680404303 :: b ~> (a ~> b)) Source # | |
Defined in Data.Foldable.Singletons |
data Foldl'Sym1 (a6989586621680404303 :: 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 a6989586621680404303 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (Foldl'Sym1 a6989586621680404303 :: TyFun b (t a ~> b) -> Type) (a6989586621680404304 :: b) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym1 a6989586621680404303 :: TyFun b (t a ~> b) -> Type) (a6989586621680404304 :: b) = Foldl'Sym2 a6989586621680404303 a6989586621680404304 :: TyFun (t a) b -> Type |
data Foldl'Sym2 (a6989586621680404303 :: b ~> (a ~> b)) (a6989586621680404304 :: 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 a6989586621680404303 a6989586621680404304 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (Foldl'Sym2 a6989586621680404303 a6989586621680404304 :: TyFun (t a) b -> Type) (a6989586621680404305 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl'Sym2 a6989586621680404303 a6989586621680404304 :: TyFun (t a) b -> Type) (a6989586621680404305 :: t a) = Foldl' a6989586621680404303 a6989586621680404304 a6989586621680404305 |
type family Foldl'Sym3 (a6989586621680404303 :: b ~> (a ~> b)) (a6989586621680404304 :: b) (a6989586621680404305 :: t a) :: b where ... Source #
Foldl'Sym3 (a6989586621680404303 :: b ~> (a ~> b)) (a6989586621680404304 :: b) (a6989586621680404305 :: t a) = Foldl' a6989586621680404303 a6989586621680404304 a6989586621680404305 |
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 suppressUnusedWarnings :: () # | |
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680404314 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons |
data Foldl1Sym1 (a6989586621680404314 :: 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 a6989586621680404314 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (Foldl1Sym1 a6989586621680404314 :: TyFun (t a) a -> Type) (a6989586621680404315 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldl1Sym1 a6989586621680404314 :: TyFun (t a) a -> Type) (a6989586621680404315 :: t a) = Foldl1 a6989586621680404314 a6989586621680404315 |
type family Foldl1Sym2 (a6989586621680404314 :: a ~> (a ~> a)) (a6989586621680404315 :: t a) :: a where ... Source #
Foldl1Sym2 (a6989586621680404314 :: a ~> (a ~> a)) (a6989586621680404315 :: t a) = Foldl1 a6989586621680404314 a6989586621680404315 |
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 suppressUnusedWarnings :: () # | |
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679824919 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679824919 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679824919 |
data Foldl1'Sym1 (a6989586621679824919 :: 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 sing :: Sing (Foldl1'Sym1 d) # | |
SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679824919 :: TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (Foldl1'Sym1 :: (a ~> (a ~> a)) -> TyFun [a] a -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (Foldl1'Sym1 a6989586621679824919 :: TyFun [a] a -> Type) (a6989586621679824920 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Foldl1'Sym1 a6989586621679824919 :: TyFun [a] a -> Type) (a6989586621679824920 :: [a]) = Foldl1' a6989586621679824919 a6989586621679824920 |
type family Foldl1'Sym2 (a6989586621679824919 :: a ~> (a ~> a)) (a6989586621679824920 :: [a]) :: a where ... Source #
Foldl1'Sym2 (a6989586621679824919 :: a ~> (a ~> a)) (a6989586621679824920 :: [a]) = Foldl1' a6989586621679824919 a6989586621679824920 |
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 suppressUnusedWarnings :: () # | |
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680404282 :: a ~> (b ~> b)) Source # | |
data FoldrSym1 (a6989586621680404282 :: 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 a6989586621680404282 :: TyFun b (t a ~> b) -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (FoldrSym1 a6989586621680404282 :: TyFun b (t a ~> b) -> Type) (a6989586621680404283 :: b) Source # | |
data FoldrSym2 (a6989586621680404282 :: a ~> (b ~> b)) (a6989586621680404283 :: 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 a6989586621680404282 a6989586621680404283 :: TyFun (t a) b -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (FoldrSym2 a6989586621680404282 a6989586621680404283 :: TyFun (t a) b -> Type) (a6989586621680404284 :: t a) Source # | |
type family FoldrSym3 (a6989586621680404282 :: a ~> (b ~> b)) (a6989586621680404283 :: b) (a6989586621680404284 :: 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 suppressUnusedWarnings :: () # | |
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680404309 :: a ~> (a ~> a)) Source # | |
Defined in Data.Foldable.Singletons |
data Foldr1Sym1 (a6989586621680404309 :: 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 a6989586621680404309 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (Foldr1Sym1 a6989586621680404309 :: TyFun (t a) a -> Type) (a6989586621680404310 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (Foldr1Sym1 a6989586621680404309 :: TyFun (t a) a -> Type) (a6989586621680404310 :: t a) = Foldr1 a6989586621680404309 a6989586621680404310 |
type family Foldr1Sym2 (a6989586621680404309 :: a ~> (a ~> a)) (a6989586621680404310 :: t a) :: a where ... Source #
Foldr1Sym2 (a6989586621680404309 :: a ~> (a ~> a)) (a6989586621680404310 :: t a) = Foldr1 a6989586621680404309 a6989586621680404310 |
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 suppressUnusedWarnings :: () # | |
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680404163 :: t [a]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680404163 :: t [a]) = Concat a6989586621680404163 |
type family ConcatSym1 (a6989586621680404163 :: t [a]) :: [a] where ... Source #
ConcatSym1 (a6989586621680404163 :: t [a]) = Concat a6989586621680404163 |
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 suppressUnusedWarnings :: () # | |
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680404152 :: a ~> [b]) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680404152 :: a ~> [b]) = ConcatMapSym1 a6989586621680404152 :: TyFun (t a) [b] -> Type |
data ConcatMapSym1 (a6989586621680404152 :: 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 a6989586621680404152 :: TyFun (t a) [b] -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (ConcatMapSym1 a6989586621680404152 :: TyFun (t a) [b] -> Type) (a6989586621680404153 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ConcatMapSym1 a6989586621680404152 :: TyFun (t a) [b] -> Type) (a6989586621680404153 :: t a) = ConcatMap a6989586621680404152 a6989586621680404153 |
type family ConcatMapSym2 (a6989586621680404152 :: a ~> [b]) (a6989586621680404153 :: t a) :: [b] where ... Source #
ConcatMapSym2 (a6989586621680404152 :: a ~> [b]) (a6989586621680404153 :: t a) = ConcatMap a6989586621680404152 a6989586621680404153 |
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 suppressUnusedWarnings :: () # | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680404147 :: 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 suppressUnusedWarnings :: () # | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680404141 :: 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 suppressUnusedWarnings :: () # | |
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680404133 :: a ~> Bool) Source # | |
data AnySym1 (a6989586621680404133 :: 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 a6989586621680404133 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (AnySym1 a6989586621680404133 :: TyFun (t a) Bool -> Type) (a6989586621680404134 :: t a) Source # | |
type family AnySym2 (a6989586621680404133 :: a ~> Bool) (a6989586621680404134 :: 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 suppressUnusedWarnings :: () # | |
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680404124 :: a ~> Bool) Source # | |
data AllSym1 (a6989586621680404124 :: 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 a6989586621680404124 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (AllSym1 a6989586621680404124 :: TyFun (t a) Bool -> Type) (a6989586621680404125 :: t a) Source # | |
type family AllSym2 (a6989586621680404124 :: a ~> Bool) (a6989586621680404125 :: t a) :: Bool where ... Source #
data SumSym0 (a1 :: TyFun (t a) a) Source #
Instances
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 suppressUnusedWarnings :: () # | |
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680404341 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680404341 :: t a) = Product a6989586621680404341 |
type family ProductSym1 (a6989586621680404341 :: t a) :: a where ... Source #
ProductSym1 (a6989586621680404341 :: t a) = Product a6989586621680404341 |
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 suppressUnusedWarnings :: () # | |
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680404332 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680404332 :: t a) = Maximum a6989586621680404332 |
type family MaximumSym1 (a6989586621680404332 :: t a) :: a where ... Source #
MaximumSym1 (a6989586621680404332 :: t a) = Maximum a6989586621680404332 |
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 suppressUnusedWarnings :: () # | |
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680404335 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680404335 :: t a) = Minimum a6989586621680404335 |
type family MinimumSym1 (a6989586621680404335 :: t a) :: a where ... Source #
MinimumSym1 (a6989586621680404335 :: t a) = Minimum a6989586621680404335 |
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 suppressUnusedWarnings :: () # | |
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679824852 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621679824852 :: 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 a6989586621679824852 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ScanlSym1 a6989586621679824852 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679824853 :: b) Source # | |
data ScanlSym2 (a6989586621679824852 :: b ~> (a ~> b)) (a6989586621679824853 :: 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 a6989586621679824852 a6989586621679824853 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ScanlSym2 a6989586621679824852 a6989586621679824853 :: TyFun [a] [b] -> Type) (a6989586621679824854 :: [a]) Source # | |
type family ScanlSym3 (a6989586621679824852 :: b ~> (a ~> b)) (a6989586621679824853 :: b) (a6989586621679824854 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679824843 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679824843 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679824843 |
data Scanl1Sym1 (a6989586621679824843 :: 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 sing :: Sing (Scanl1Sym1 d) # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621679824843 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (Scanl1Sym1 a6989586621679824843 :: TyFun [a] [a] -> Type) (a6989586621679824844 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanl1Sym1 a6989586621679824843 :: TyFun [a] [a] -> Type) (a6989586621679824844 :: [a]) = Scanl1 a6989586621679824843 a6989586621679824844 |
type family Scanl1Sym2 (a6989586621679824843 :: a ~> (a ~> a)) (a6989586621679824844 :: [a]) :: [a] where ... Source #
Scanl1Sym2 (a6989586621679824843 :: a ~> (a ~> a)) (a6989586621679824844 :: [a]) = Scanl1 a6989586621679824843 a6989586621679824844 |
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 suppressUnusedWarnings :: () # | |
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679824825 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621679824825 :: 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 a6989586621679824825 :: TyFun b ([a] ~> [b]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ScanrSym1 a6989586621679824825 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679824826 :: b) Source # | |
data ScanrSym2 (a6989586621679824825 :: a ~> (b ~> b)) (a6989586621679824826 :: 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 a6989586621679824825 a6989586621679824826 :: TyFun [a] [b] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ScanrSym2 a6989586621679824825 a6989586621679824826 :: TyFun [a] [b] -> Type) (a6989586621679824827 :: [a]) Source # | |
type family ScanrSym3 (a6989586621679824825 :: a ~> (b ~> b)) (a6989586621679824826 :: b) (a6989586621679824827 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679824805 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679824805 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679824805 |
data Scanr1Sym1 (a6989586621679824805 :: 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 sing :: Sing (Scanr1Sym1 d) # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621679824805 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (Scanr1Sym1 a6989586621679824805 :: TyFun [a] [a] -> Type) (a6989586621679824806 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Scanr1Sym1 a6989586621679824805 :: TyFun [a] [a] -> Type) (a6989586621679824806 :: [a]) = Scanr1 a6989586621679824805 a6989586621679824806 |
type family Scanr1Sym2 (a6989586621679824805 :: a ~> (a ~> a)) (a6989586621679824806 :: [a]) :: [a] where ... Source #
Scanr1Sym2 (a6989586621679824805 :: a ~> (a ~> a)) (a6989586621679824806 :: [a]) = Scanr1 a6989586621679824805 a6989586621679824806 |
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 suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680756735 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons |
data MapAccumLSym1 (a6989586621680756735 :: 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 a6989586621680756735 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym1 a6989586621680756735 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680756736 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym1 a6989586621680756735 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680756736 :: a) = MapAccumLSym2 a6989586621680756735 a6989586621680756736 :: TyFun (t b) (a, t c) -> Type |
data MapAccumLSym2 (a6989586621680756735 :: a ~> (b ~> (a, c))) (a6989586621680756736 :: 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 a6989586621680756735 a6989586621680756736 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MapAccumLSym2 a6989586621680756735 a6989586621680756736 :: TyFun (t b) (a, t c) -> Type) (a6989586621680756737 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumLSym2 a6989586621680756735 a6989586621680756736 :: TyFun (t b) (a, t c) -> Type) (a6989586621680756737 :: t b) = MapAccumL a6989586621680756735 a6989586621680756736 a6989586621680756737 |
type family MapAccumLSym3 (a6989586621680756735 :: a ~> (b ~> (a, c))) (a6989586621680756736 :: a) (a6989586621680756737 :: t b) :: (a, t c) where ... Source #
MapAccumLSym3 (a6989586621680756735 :: a ~> (b ~> (a, c))) (a6989586621680756736 :: a) (a6989586621680756737 :: t b) = MapAccumL a6989586621680756735 a6989586621680756736 a6989586621680756737 |
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 suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680756725 :: a ~> (b ~> (a, c))) Source # | |
Defined in Data.Traversable.Singletons |
data MapAccumRSym1 (a6989586621680756725 :: 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 a6989586621680756725 :: TyFun a (t b ~> (a, t c)) -> Type) Source # | |
Defined in Data.Traversable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym1 a6989586621680756725 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680756726 :: a) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym1 a6989586621680756725 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680756726 :: a) = MapAccumRSym2 a6989586621680756725 a6989586621680756726 :: TyFun (t b) (a, t c) -> Type |
data MapAccumRSym2 (a6989586621680756725 :: a ~> (b ~> (a, c))) (a6989586621680756726 :: 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 a6989586621680756725 a6989586621680756726 :: TyFun (t b) (a, t c) -> Type) Source # | |
Defined in Data.Traversable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MapAccumRSym2 a6989586621680756725 a6989586621680756726 :: TyFun (t b) (a, t c) -> Type) (a6989586621680756727 :: t b) Source # | |
Defined in Data.Traversable.Singletons type Apply (MapAccumRSym2 a6989586621680756725 a6989586621680756726 :: TyFun (t b) (a, t c) -> Type) (a6989586621680756727 :: t b) = MapAccumR a6989586621680756725 a6989586621680756726 a6989586621680756727 |
type family MapAccumRSym3 (a6989586621680756725 :: a ~> (b ~> (a, c))) (a6989586621680756726 :: a) (a6989586621680756727 :: t b) :: (a, t c) where ... Source #
MapAccumRSym3 (a6989586621680756725 :: a ~> (b ~> (a, c))) (a6989586621680756726 :: a) (a6989586621680756727 :: t b) = MapAccumR a6989586621680756725 a6989586621680756726 a6989586621680756727 |
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 suppressUnusedWarnings :: () # | |
type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679823942 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679823942 :: Natural) = ReplicateSym1 a6989586621679823942 :: TyFun a [a] -> Type |
data ReplicateSym1 (a6989586621679823942 :: 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 a6989586621679823942 :: TyFun a [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ReplicateSym1 a6989586621679823942 :: TyFun a [a] -> Type) (a6989586621679823943 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ReplicateSym1 a6989586621679823942 :: TyFun a [a] -> Type) (a6989586621679823943 :: a) = Replicate a6989586621679823942 a6989586621679823943 |
type family ReplicateSym2 (a6989586621679823942 :: Natural) (a6989586621679823943 :: a) :: [a] where ... Source #
ReplicateSym2 a6989586621679823942 (a6989586621679823943 :: a) = Replicate a6989586621679823942 a6989586621679823943 |
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 suppressUnusedWarnings :: () # | |
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679824697 :: b ~> Maybe (a, b)) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679824697 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679824697 |
data UnfoldrSym1 (a6989586621679824697 :: 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 sing :: Sing (UnfoldrSym1 d) # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621679824697 :: TyFun b [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (UnfoldrSym1 a6989586621679824697 :: TyFun b [a] -> Type) (a6989586621679824698 :: b) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnfoldrSym1 a6989586621679824697 :: TyFun b [a] -> Type) (a6989586621679824698 :: b) = Unfoldr a6989586621679824697 a6989586621679824698 |
type family UnfoldrSym2 (a6989586621679824697 :: b ~> Maybe (a, b)) (a6989586621679824698 :: b) :: [a] where ... Source #
UnfoldrSym2 (a6989586621679824697 :: b ~> Maybe (a, b)) (a6989586621679824698 :: b) = Unfoldr a6989586621679824697 a6989586621679824698 |
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 suppressUnusedWarnings :: () # | |
type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679824097 :: Natural) Source # | |
data TakeSym1 (a6989586621679824097 :: 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 a6989586621679824097 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (TakeSym1 a6989586621679824097 :: TyFun [a] [a] -> Type) (a6989586621679824098 :: [a]) Source # | |
type family TakeSym2 (a6989586621679824097 :: Natural) (a6989586621679824098 :: [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 suppressUnusedWarnings :: () # | |
type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679824084 :: Natural) Source # | |
data DropSym1 (a6989586621679824084 :: 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 a6989586621679824084 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (DropSym1 a6989586621679824084 :: TyFun [a] [a] -> Type) (a6989586621679824085 :: [a]) Source # | |
type family DropSym2 (a6989586621679824084 :: Natural) (a6989586621679824085 :: [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 suppressUnusedWarnings :: () # | |
type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679824077 :: Natural) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679824077 :: Natural) = SplitAtSym1 a6989586621679824077 :: TyFun [a] ([a], [a]) -> Type |
data SplitAtSym1 (a6989586621679824077 :: 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 a6989586621679824077 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (SplitAtSym1 a6989586621679824077 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679824078 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SplitAtSym1 a6989586621679824077 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679824078 :: [a]) = SplitAt a6989586621679824077 a6989586621679824078 |
type family SplitAtSym2 (a6989586621679824077 :: Natural) (a6989586621679824078 :: [a]) :: ([a], [a]) where ... Source #
SplitAtSym2 a6989586621679824077 (a6989586621679824078 :: [a]) = SplitAt a6989586621679824077 a6989586621679824078 |
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 suppressUnusedWarnings :: () # | |
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824214 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824214 :: a ~> Bool) = TakeWhileSym1 a6989586621679824214 |
data TakeWhileSym1 (a6989586621679824214 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing (TakeWhileSym1 d) # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621679824214 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (TakeWhileSym1 a6989586621679824214 :: TyFun [a] [a] -> Type) (a6989586621679824215 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (TakeWhileSym1 a6989586621679824214 :: TyFun [a] [a] -> Type) (a6989586621679824215 :: [a]) = TakeWhile a6989586621679824214 a6989586621679824215 |
type family TakeWhileSym2 (a6989586621679824214 :: a ~> Bool) (a6989586621679824215 :: [a]) :: [a] where ... Source #
TakeWhileSym2 (a6989586621679824214 :: a ~> Bool) (a6989586621679824215 :: [a]) = TakeWhile a6989586621679824214 a6989586621679824215 |
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 suppressUnusedWarnings :: () # | |
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824199 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824199 :: a ~> Bool) = DropWhileSym1 a6989586621679824199 |
data DropWhileSym1 (a6989586621679824199 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing (DropWhileSym1 d) # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621679824199 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (DropWhileSym1 a6989586621679824199 :: TyFun [a] [a] -> Type) (a6989586621679824200 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileSym1 a6989586621679824199 :: TyFun [a] [a] -> Type) (a6989586621679824200 :: [a]) = DropWhile a6989586621679824199 a6989586621679824200 |
type family DropWhileSym2 (a6989586621679824199 :: a ~> Bool) (a6989586621679824200 :: [a]) :: [a] where ... Source #
DropWhileSym2 (a6989586621679824199 :: a ~> Bool) (a6989586621679824200 :: [a]) = DropWhile a6989586621679824199 a6989586621679824200 |
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 suppressUnusedWarnings :: () # | |
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824182 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824182 :: a ~> Bool) = DropWhileEndSym1 a6989586621679824182 |
data DropWhileEndSym1 (a6989586621679824182 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing (DropWhileEndSym1 d) # | |
SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679824182 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (DropWhileEndSym1 a6989586621679824182 :: TyFun [a] [a] -> Type) (a6989586621679824183 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DropWhileEndSym1 a6989586621679824182 :: TyFun [a] [a] -> Type) (a6989586621679824183 :: [a]) = DropWhileEnd a6989586621679824182 a6989586621679824183 |
type family DropWhileEndSym2 (a6989586621679824182 :: a ~> Bool) (a6989586621679824183 :: [a]) :: [a] where ... Source #
DropWhileEndSym2 (a6989586621679824182 :: a ~> Bool) (a6989586621679824183 :: [a]) = DropWhileEnd a6989586621679824182 a6989586621679824183 |
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 suppressUnusedWarnings :: () # | |
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679824145 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621679824145 :: 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 a6989586621679824145 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
type Apply (SpanSym1 a6989586621679824145 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679824146 :: [a]) Source # | |
type family SpanSym2 (a6989586621679824145 :: a ~> Bool) (a6989586621679824146 :: [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 suppressUnusedWarnings :: () # | |
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679824110 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621679824110 :: 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 a6989586621679824110 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
type Apply (BreakSym1 a6989586621679824110 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679824111 :: [a]) Source # | |
type family BreakSym2 (a6989586621679824110 :: a ~> Bool) (a6989586621679824111 :: [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 suppressUnusedWarnings :: () # | |
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679975077 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679975077 :: [a]) = StripPrefixSym1 a6989586621679975077 |
data StripPrefixSym1 (a6989586621679975077 :: [a]) (b :: TyFun [a] (Maybe [a])) Source #
Instances
SuppressUnusedWarnings (StripPrefixSym1 a6989586621679975077 :: TyFun [a] (Maybe [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (StripPrefixSym1 a6989586621679975077 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679975078 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (StripPrefixSym1 a6989586621679975077 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679975078 :: [a]) = StripPrefix a6989586621679975077 a6989586621679975078 |
type family StripPrefixSym2 (a6989586621679975077 :: [a]) (a6989586621679975078 :: [a]) :: Maybe [a] where ... Source #
StripPrefixSym2 (a6989586621679975077 :: [a]) (a6989586621679975078 :: [a]) = StripPrefix a6989586621679975077 a6989586621679975078 |
data GroupSym0 (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 suppressUnusedWarnings :: () # | |
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824671 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824671 :: [a]) = IsPrefixOfSym1 a6989586621679824671 |
data IsPrefixOfSym1 (a6989586621679824671 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IsPrefixOfSym1 d) # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679824671 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IsPrefixOfSym1 a6989586621679824671 :: TyFun [a] Bool -> Type) (a6989586621679824672 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsPrefixOfSym1 a6989586621679824671 :: TyFun [a] Bool -> Type) (a6989586621679824672 :: [a]) = IsPrefixOf a6989586621679824671 a6989586621679824672 |
type family IsPrefixOfSym2 (a6989586621679824671 :: [a]) (a6989586621679824672 :: [a]) :: Bool where ... Source #
IsPrefixOfSym2 (a6989586621679824671 :: [a]) (a6989586621679824672 :: [a]) = IsPrefixOf a6989586621679824671 a6989586621679824672 |
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 suppressUnusedWarnings :: () # | |
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824664 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824664 :: [a]) = IsSuffixOfSym1 a6989586621679824664 |
data IsSuffixOfSym1 (a6989586621679824664 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
SEq a => SingI1 (IsSuffixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IsSuffixOfSym1 d) # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679824664 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IsSuffixOfSym1 a6989586621679824664 :: TyFun [a] Bool -> Type) (a6989586621679824665 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsSuffixOfSym1 a6989586621679824664 :: TyFun [a] Bool -> Type) (a6989586621679824665 :: [a]) = IsSuffixOf a6989586621679824664 a6989586621679824665 |
type family IsSuffixOfSym2 (a6989586621679824664 :: [a]) (a6989586621679824665 :: [a]) :: Bool where ... Source #
IsSuffixOfSym2 (a6989586621679824664 :: [a]) (a6989586621679824665 :: [a]) = IsSuffixOf a6989586621679824664 a6989586621679824665 |
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 suppressUnusedWarnings :: () # | |
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824657 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679824657 :: [a]) = IsInfixOfSym1 a6989586621679824657 |
data IsInfixOfSym1 (a6989586621679824657 :: [a]) (b :: TyFun [a] Bool) Source #
Instances
SEq a => SingI1 (IsInfixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IsInfixOfSym1 d) # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679824657 :: TyFun [a] Bool -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IsInfixOfSym1 a6989586621679824657 :: TyFun [a] Bool -> Type) (a6989586621679824658 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal |
type family IsInfixOfSym2 (a6989586621679824657 :: [a]) (a6989586621679824658 :: [a]) :: Bool where ... Source #
IsInfixOfSym2 (a6989586621679824657 :: [a]) (a6989586621679824658 :: [a]) = IsInfixOf a6989586621679824657 a6989586621679824658 |
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 suppressUnusedWarnings :: () # | |
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680404328 :: a) Source # | |
data ElemSym1 (a6989586621680404328 :: 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 a6989586621680404328 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (ElemSym1 a6989586621680404328 :: TyFun (t a) Bool -> Type) (a6989586621680404329 :: t a) Source # | |
type family ElemSym2 (a6989586621680404328 :: a) (a6989586621680404329 :: 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 suppressUnusedWarnings :: () # | |
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680404075 :: a) Source # | |
Defined in Data.Foldable.Singletons type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680404075 :: a) = NotElemSym1 a6989586621680404075 :: TyFun (t a) Bool -> Type |
data NotElemSym1 (a6989586621680404075 :: 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 a6989586621680404075 :: TyFun (t a) Bool -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (NotElemSym1 a6989586621680404075 :: TyFun (t a) Bool -> Type) (a6989586621680404076 :: t a) Source # | |
Defined in Data.Foldable.Singletons |
type family NotElemSym2 (a6989586621680404075 :: a) (a6989586621680404076 :: t a) :: Bool where ... Source #
NotElemSym2 (a6989586621680404075 :: a) (a6989586621680404076 :: t a) = NotElem a6989586621680404075 a6989586621680404076 |
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 suppressUnusedWarnings :: () # | |
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679824005 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679824005 :: a) = LookupSym1 a6989586621679824005 :: TyFun [(a, b)] (Maybe b) -> Type |
data LookupSym1 (a6989586621679824005 :: 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 a6989586621679824005 :: TyFun [(a, b)] (Maybe b) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (LookupSym1 a6989586621679824005 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679824006 :: [(a, b)]) Source # | |
Defined in Data.List.Singletons.Internal |
type family LookupSym2 (a6989586621679824005 :: a) (a6989586621679824006 :: [(a, b)]) :: Maybe b where ... Source #
LookupSym2 (a6989586621679824005 :: a) (a6989586621679824006 :: [(a, b)]) = Lookup a6989586621679824005 a6989586621679824006 |
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 suppressUnusedWarnings :: () # | |
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680404057 :: a ~> Bool) Source # | |
data FindSym1 (a6989586621680404057 :: 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 a6989586621680404057 :: TyFun (t a) (Maybe a) -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (FindSym1 a6989586621680404057 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680404058 :: t a) Source # | |
type family FindSym2 (a6989586621680404057 :: a ~> Bool) (a6989586621680404058 :: 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 suppressUnusedWarnings :: () # | |
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824314 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679824314 :: a ~> Bool) = FilterSym1 a6989586621679824314 |
data FilterSym1 (a6989586621679824314 :: a ~> Bool) (b :: TyFun [a] [a]) Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing (FilterSym1 d) # | |
SuppressUnusedWarnings (FilterSym1 a6989586621679824314 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (FilterSym1 a6989586621679824314 :: TyFun [a] [a] -> Type) (a6989586621679824315 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FilterSym1 a6989586621679824314 :: TyFun [a] [a] -> Type) (a6989586621679824315 :: [a]) = Filter a6989586621679824314 a6989586621679824315 |
type family FilterSym2 (a6989586621679824314 :: a ~> Bool) (a6989586621679824315 :: [a]) :: [a] where ... Source #
FilterSym2 (a6989586621679824314 :: a ~> Bool) (a6989586621679824315 :: [a]) = Filter a6989586621679824314 a6989586621679824315 |
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 suppressUnusedWarnings :: () # | |
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679823998 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679823998 :: a ~> Bool) = PartitionSym1 a6989586621679823998 |
data PartitionSym1 (a6989586621679823998 :: 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 sing :: Sing (PartitionSym1 d) # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621679823998 :: TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (PartitionSym1 a6989586621679823998 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679823999 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (PartitionSym1 a6989586621679823998 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679823999 :: [a]) = Partition a6989586621679823998 a6989586621679823999 |
type family PartitionSym2 (a6989586621679823998 :: a ~> Bool) (a6989586621679823999 :: [a]) :: ([a], [a]) where ... Source #
PartitionSym2 (a6989586621679823998 :: a ~> Bool) (a6989586621679823999 :: [a]) = Partition a6989586621679823998 a6989586621679823999 |
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 suppressUnusedWarnings :: () # | |
type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679823922 :: [a]) Source # | |
data (a6989586621679823922 :: [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 ((!!@#@$$) a6989586621679823922 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply ((!!@#@$$) a6989586621679823922 :: TyFun Natural a -> Type) (a6989586621679823923 :: Natural) Source # | |
type family (a6989586621679823922 :: [a]) !!@#@$$$ (a6989586621679823923 :: 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 suppressUnusedWarnings :: () # | |
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679824298 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679824298 :: a) = ElemIndexSym1 a6989586621679824298 |
data ElemIndexSym1 (a6989586621679824298 :: 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 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 sing :: Sing (ElemIndexSym1 d) # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679824298 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ElemIndexSym1 a6989586621679824298 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679824299 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal |
type family ElemIndexSym2 (a6989586621679824298 :: a) (a6989586621679824299 :: [a]) :: Maybe Natural where ... Source #
ElemIndexSym2 (a6989586621679824298 :: a) (a6989586621679824299 :: [a]) = ElemIndex a6989586621679824298 a6989586621679824299 |
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 suppressUnusedWarnings :: () # | |
type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679824289 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679824289 :: a) = ElemIndicesSym1 a6989586621679824289 |
data ElemIndicesSym1 (a6989586621679824289 :: a) (b :: TyFun [a] [Natural]) Source #
Instances
SEq a => SingI1 (ElemIndicesSym1 :: a -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (ElemIndicesSym1 d) # | |
SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679824289 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ElemIndicesSym1 a6989586621679824289 :: TyFun [a] [Natural] -> Type) (a6989586621679824290 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ElemIndicesSym1 a6989586621679824289 :: TyFun [a] [Natural] -> Type) (a6989586621679824290 :: [a]) = ElemIndices a6989586621679824289 a6989586621679824290 |
type family ElemIndicesSym2 (a6989586621679824289 :: a) (a6989586621679824290 :: [a]) :: [Natural] where ... Source #
ElemIndicesSym2 (a6989586621679824289 :: a) (a6989586621679824290 :: [a]) = ElemIndices a6989586621679824289 a6989586621679824290 |
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 suppressUnusedWarnings :: () # | |
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679824280 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal |
data FindIndexSym1 (a6989586621679824280 :: 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 sing :: Sing (FindIndexSym1 d) # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679824280 :: TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (FindIndexSym1 :: (a ~> Bool) -> TyFun [a] (Maybe Natural) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (FindIndexSym1 a6989586621679824280 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679824281 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal |
type family FindIndexSym2 (a6989586621679824280 :: a ~> Bool) (a6989586621679824281 :: [a]) :: Maybe Natural where ... Source #
FindIndexSym2 (a6989586621679824280 :: a ~> Bool) (a6989586621679824281 :: [a]) = FindIndex a6989586621679824280 a6989586621679824281 |
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 suppressUnusedWarnings :: () # | |
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679824257 :: a ~> Bool) Source # | |
Defined in Data.List.Singletons.Internal |
data FindIndicesSym1 (a6989586621679824257 :: a ~> Bool) (b :: TyFun [a] [Natural]) Source #
Instances
SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing (FindIndicesSym1 d) # | |
SuppressUnusedWarnings (FindIndicesSym1 a6989586621679824257 :: TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (FindIndicesSym1 :: (a ~> Bool) -> TyFun [a] [Natural] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (FindIndicesSym1 a6989586621679824257 :: TyFun [a] [Natural] -> Type) (a6989586621679824258 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (FindIndicesSym1 a6989586621679824257 :: TyFun [a] [Natural] -> Type) (a6989586621679824258 :: [a]) = FindIndices a6989586621679824257 a6989586621679824258 |
type family FindIndicesSym2 (a6989586621679824257 :: a ~> Bool) (a6989586621679824258 :: [a]) :: [Natural] where ... Source #
FindIndicesSym2 (a6989586621679824257 :: a ~> Bool) (a6989586621679824258 :: [a]) = FindIndices a6989586621679824257 a6989586621679824258 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679824632 :: [a]) Source # | |
data ZipSym1 (a6989586621679824632 :: [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 a6989586621679824632 :: TyFun [b] [(a, b)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipSym1 a6989586621679824632 :: TyFun [b] [(a, b)] -> Type) (a6989586621679824633 :: [b]) Source # | |
type family ZipSym2 (a6989586621679824632 :: [a]) (a6989586621679824633 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679824620 :: [a]) Source # | |
data Zip3Sym1 (a6989586621679824620 :: [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 a6989586621679824620 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip3Sym1 a6989586621679824620 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679824621 :: [b]) Source # | |
data Zip3Sym2 (a6989586621679824620 :: [a]) (a6989586621679824621 :: [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 a6989586621679824620 a6989586621679824621 :: TyFun [c] [(a, b, c)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip3Sym2 a6989586621679824620 a6989586621679824621 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679824622 :: [c]) Source # | |
type family Zip3Sym3 (a6989586621679824620 :: [a]) (a6989586621679824621 :: [b]) (a6989586621679824622 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679975066 :: [a]) Source # | |
data Zip4Sym1 (a6989586621679975066 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)]))) Source #
Instances
SuppressUnusedWarnings (Zip4Sym1 a6989586621679975066 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip4Sym1 a6989586621679975066 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679975067 :: [b]) Source # | |
data Zip4Sym2 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (c1 :: TyFun [c] ([d] ~> [(a, b, c, d)])) Source #
Instances
SuppressUnusedWarnings (Zip4Sym2 a6989586621679975066 a6989586621679975067 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip4Sym2 a6989586621679975066 a6989586621679975067 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679975068 :: [c]) Source # | |
data Zip4Sym3 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (a6989586621679975068 :: [c]) (d1 :: TyFun [d] [(a, b, c, d)]) Source #
Instances
SuppressUnusedWarnings (Zip4Sym3 a6989586621679975066 a6989586621679975067 a6989586621679975068 :: TyFun [d] [(a, b, c, d)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip4Sym3 a6989586621679975066 a6989586621679975067 a6989586621679975068 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679975069 :: [d]) Source # | |
type family Zip4Sym4 (a6989586621679975066 :: [a]) (a6989586621679975067 :: [b]) (a6989586621679975068 :: [c]) (a6989586621679975069 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679975043 :: [a]) Source # | |
data Zip5Sym1 (a6989586621679975043 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym1 a6989586621679975043 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip5Sym1 a6989586621679975043 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679975044 :: [b]) Source # | |
data Zip5Sym2 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)]))) Source #
Instances
SuppressUnusedWarnings (Zip5Sym2 a6989586621679975043 a6989586621679975044 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip5Sym2 a6989586621679975043 a6989586621679975044 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679975045 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip5Sym3 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (d1 :: TyFun [d] ([e] ~> [(a, b, c, d, e)])) Source #
Instances
SuppressUnusedWarnings (Zip5Sym3 a6989586621679975043 a6989586621679975044 a6989586621679975045 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip5Sym3 a6989586621679975043 a6989586621679975044 a6989586621679975045 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679975046 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip5Sym4 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (a6989586621679975046 :: [d]) (e1 :: TyFun [e] [(a, b, c, d, e)]) Source #
Instances
SuppressUnusedWarnings (Zip5Sym4 a6989586621679975043 a6989586621679975044 a6989586621679975045 a6989586621679975046 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip5Sym4 a6989586621679975043 a6989586621679975044 a6989586621679975045 a6989586621679975046 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679975047 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal |
type family Zip5Sym5 (a6989586621679975043 :: [a]) (a6989586621679975044 :: [b]) (a6989586621679975045 :: [c]) (a6989586621679975046 :: [d]) (a6989586621679975047 :: [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 suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679975015 :: [a]) Source # | |
data Zip6Sym1 (a6989586621679975015 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym1 a6989586621679975015 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym1 a6989586621679975015 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679975016 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip6Sym2 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym2 a6989586621679975015 a6989586621679975016 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym2 a6989586621679975015 a6989586621679975016 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679975017 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip6Sym3 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) Source #
Instances
SuppressUnusedWarnings (Zip6Sym3 a6989586621679975015 a6989586621679975016 a6989586621679975017 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym3 a6989586621679975015 a6989586621679975016 a6989586621679975017 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679975018 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym3 a6989586621679975015 a6989586621679975016 a6989586621679975017 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679975018 :: [d]) = Zip6Sym4 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type |
data Zip6Sym4 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (e1 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)])) Source #
Instances
SuppressUnusedWarnings (Zip6Sym4 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym4 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679975019 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym4 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679975019 :: [e]) = Zip6Sym5 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 :: TyFun [f] [(a, b, c, d, e, f)] -> Type |
data Zip6Sym5 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (a6989586621679975019 :: [e]) (f1 :: TyFun [f] [(a, b, c, d, e, f)]) Source #
Instances
SuppressUnusedWarnings (Zip6Sym5 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip6Sym5 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679975020 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip6Sym5 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679975020 :: [f]) = Zip6 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 a6989586621679975020 |
type family Zip6Sym6 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (a6989586621679975019 :: [e]) (a6989586621679975020 :: [f]) :: [(a, b, c, d, e, f)] where ... Source #
Zip6Sym6 (a6989586621679975015 :: [a]) (a6989586621679975016 :: [b]) (a6989586621679975017 :: [c]) (a6989586621679975018 :: [d]) (a6989586621679975019 :: [e]) (a6989586621679975020 :: [f]) = Zip6 a6989586621679975015 a6989586621679975016 a6989586621679975017 a6989586621679975018 a6989586621679975019 a6989586621679975020 |
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 suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679974982 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip7Sym1 (a6989586621679974982 :: [a]) (b1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym1 a6989586621679974982 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym1 a6989586621679974982 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679974983 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal |
data Zip7Sym2 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (c1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym2 a6989586621679974982 a6989586621679974983 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym2 a6989586621679974982 a6989586621679974983 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679974984 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym2 a6989586621679974982 a6989586621679974983 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679974984 :: [c]) = Zip7Sym3 a6989586621679974982 a6989586621679974983 a6989586621679974984 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type |
data Zip7Sym3 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (d1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym3 a6989586621679974982 a6989586621679974983 a6989586621679974984 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym3 a6989586621679974982 a6989586621679974983 a6989586621679974984 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679974985 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym3 a6989586621679974982 a6989586621679974983 a6989586621679974984 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679974985 :: [d]) = Zip7Sym4 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type |
data Zip7Sym4 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (e1 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) Source #
Instances
SuppressUnusedWarnings (Zip7Sym4 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym4 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679974986 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym4 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679974986 :: [e]) = Zip7Sym5 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type |
data Zip7Sym5 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (f1 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)])) Source #
Instances
SuppressUnusedWarnings (Zip7Sym5 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym5 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679974987 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym5 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679974987 :: [f]) = Zip7Sym6 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type |
data Zip7Sym6 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (a6989586621679974987 :: [f]) (g1 :: TyFun [g] [(a, b, c, d, e, f, g)]) Source #
Instances
SuppressUnusedWarnings (Zip7Sym6 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (Zip7Sym6 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679974988 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Zip7Sym6 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679974988 :: [g]) = Zip7 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 a6989586621679974988 |
type family Zip7Sym7 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (a6989586621679974987 :: [f]) (a6989586621679974988 :: [g]) :: [(a, b, c, d, e, f, g)] where ... Source #
Zip7Sym7 (a6989586621679974982 :: [a]) (a6989586621679974983 :: [b]) (a6989586621679974984 :: [c]) (a6989586621679974985 :: [d]) (a6989586621679974986 :: [e]) (a6989586621679974987 :: [f]) (a6989586621679974988 :: [g]) = Zip7 a6989586621679974982 a6989586621679974983 a6989586621679974984 a6989586621679974985 a6989586621679974986 a6989586621679974987 a6989586621679974988 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679824608 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.Singletons.Internal |
data ZipWithSym1 (a6989586621679824608 :: 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 sing :: Sing (ZipWithSym1 d) # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621679824608 :: TyFun [a] ([b] ~> [c]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym1 a6989586621679824608 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679824609 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym1 a6989586621679824608 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679824609 :: [a]) = ZipWithSym2 a6989586621679824608 a6989586621679824609 |
data ZipWithSym2 (a6989586621679824608 :: a ~> (b ~> c)) (a6989586621679824609 :: [a]) (c1 :: TyFun [b] [c]) Source #
Instances
SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (ZipWithSym2 d1 d2) # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621679824608 a6989586621679824609 :: TyFun [b] [c] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym2 a6989586621679824608 a6989586621679824609 :: TyFun [b] [c] -> Type) (a6989586621679824610 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWithSym2 a6989586621679824608 a6989586621679824609 :: TyFun [b] [c] -> Type) (a6989586621679824610 :: [b]) = ZipWith a6989586621679824608 a6989586621679824609 a6989586621679824610 |
type family ZipWithSym3 (a6989586621679824608 :: a ~> (b ~> c)) (a6989586621679824609 :: [a]) (a6989586621679824610 :: [b]) :: [c] where ... Source #
ZipWithSym3 (a6989586621679824608 :: a ~> (b ~> c)) (a6989586621679824609 :: [a]) (a6989586621679824610 :: [b]) = ZipWith a6989586621679824608 a6989586621679824609 a6989586621679824610 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679824593 :: a ~> (b ~> (c ~> d))) Source # | |
Defined in Data.List.Singletons.Internal |
data ZipWith3Sym1 (a6989586621679824593 :: 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 sing :: Sing (ZipWith3Sym1 d2) # | |
SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679824593 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith3Sym1 a6989586621679824593 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679824594 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym1 a6989586621679824593 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679824594 :: [a]) = ZipWith3Sym2 a6989586621679824593 a6989586621679824594 |
data ZipWith3Sym2 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [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 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 sing :: Sing (ZipWith3Sym2 d2 d3) # | |
SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679824593 a6989586621679824594 :: TyFun [b] ([c] ~> [d]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith3Sym2 a6989586621679824593 a6989586621679824594 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679824595 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym2 a6989586621679824593 a6989586621679824594 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679824595 :: [b]) = ZipWith3Sym3 a6989586621679824593 a6989586621679824594 a6989586621679824595 |
data ZipWith3Sym3 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (a6989586621679824595 :: [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 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 sing :: Sing (ZipWith3Sym3 d2 d3 d4) # | |
SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679824593 a6989586621679824594 a6989586621679824595 :: TyFun [c] [d] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith3Sym3 a6989586621679824593 a6989586621679824594 a6989586621679824595 :: TyFun [c] [d] -> Type) (a6989586621679824596 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith3Sym3 a6989586621679824593 a6989586621679824594 a6989586621679824595 :: TyFun [c] [d] -> Type) (a6989586621679824596 :: [c]) = ZipWith3 a6989586621679824593 a6989586621679824594 a6989586621679824595 a6989586621679824596 |
type family ZipWith3Sym4 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (a6989586621679824595 :: [b]) (a6989586621679824596 :: [c]) :: [d] where ... Source #
ZipWith3Sym4 (a6989586621679824593 :: a ~> (b ~> (c ~> d))) (a6989586621679824594 :: [a]) (a6989586621679824595 :: [b]) (a6989586621679824596 :: [c]) = ZipWith3 a6989586621679824593 a6989586621679824594 a6989586621679824595 a6989586621679824596 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) Source # | |
data ZipWith4Sym1 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e])))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym1 a6989586621679974946 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith4Sym1 a6989586621679974946 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679974947 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym1 a6989586621679974946 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679974947 :: [a]) = ZipWith4Sym2 a6989586621679974946 a6989586621679974947 |
data ZipWith4Sym2 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> [e]))) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679974946 a6989586621679974947 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith4Sym2 a6989586621679974946 a6989586621679974947 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679974948 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym2 a6989586621679974946 a6989586621679974947 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679974948 :: [b]) = ZipWith4Sym3 a6989586621679974946 a6989586621679974947 a6989586621679974948 |
data ZipWith4Sym3 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (d1 :: TyFun [c] ([d] ~> [e])) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679974946 a6989586621679974947 a6989586621679974948 :: TyFun [c] ([d] ~> [e]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith4Sym3 a6989586621679974946 a6989586621679974947 a6989586621679974948 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679974949 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym3 a6989586621679974946 a6989586621679974947 a6989586621679974948 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679974949 :: [c]) = ZipWith4Sym4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 |
data ZipWith4Sym4 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (a6989586621679974949 :: [c]) (e1 :: TyFun [d] [e]) Source #
Instances
SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 :: TyFun [d] [e] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith4Sym4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 :: TyFun [d] [e] -> Type) (a6989586621679974950 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith4Sym4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 :: TyFun [d] [e] -> Type) (a6989586621679974950 :: [d]) = ZipWith4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 a6989586621679974950 |
type family ZipWith4Sym5 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (a6989586621679974949 :: [c]) (a6989586621679974950 :: [d]) :: [e] where ... Source #
ZipWith4Sym5 (a6989586621679974946 :: a ~> (b ~> (c ~> (d ~> e)))) (a6989586621679974947 :: [a]) (a6989586621679974948 :: [b]) (a6989586621679974949 :: [c]) (a6989586621679974950 :: [d]) = ZipWith4 a6989586621679974946 a6989586621679974947 a6989586621679974948 a6989586621679974949 a6989586621679974950 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # | |
data ZipWith5Sym1 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym1 a6989586621679974923 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym1 a6989586621679974923 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679974924 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym1 a6989586621679974923 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679974924 :: [a]) = ZipWith5Sym2 a6989586621679974923 a6989586621679974924 |
data ZipWith5Sym2 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f])))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym2 a6989586621679974923 a6989586621679974924 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym2 a6989586621679974923 a6989586621679974924 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679974925 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym2 a6989586621679974923 a6989586621679974924 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679974925 :: [b]) = ZipWith5Sym3 a6989586621679974923 a6989586621679974924 a6989586621679974925 |
data ZipWith5Sym3 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> [f]))) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym3 a6989586621679974923 a6989586621679974924 a6989586621679974925 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym3 a6989586621679974923 a6989586621679974924 a6989586621679974925 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679974926 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym3 a6989586621679974923 a6989586621679974924 a6989586621679974925 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679974926 :: [c]) = ZipWith5Sym4 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 |
data ZipWith5Sym4 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (e1 :: TyFun [d] ([e] ~> [f])) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 :: TyFun [d] ([e] ~> [f]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym4 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679974927 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym4 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679974927 :: [d]) = ZipWith5Sym5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 |
data ZipWith5Sym5 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (a6989586621679974927 :: [d]) (f1 :: TyFun [e] [f]) Source #
Instances
SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 :: TyFun [e] [f] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith5Sym5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 :: TyFun [e] [f] -> Type) (a6989586621679974928 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith5Sym5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 :: TyFun [e] [f] -> Type) (a6989586621679974928 :: [e]) = ZipWith5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 a6989586621679974928 |
type family ZipWith5Sym6 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (a6989586621679974927 :: [d]) (a6989586621679974928 :: [e]) :: [f] where ... Source #
ZipWith5Sym6 (a6989586621679974923 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) (a6989586621679974924 :: [a]) (a6989586621679974925 :: [b]) (a6989586621679974926 :: [c]) (a6989586621679974927 :: [d]) (a6989586621679974928 :: [e]) = ZipWith5 a6989586621679974923 a6989586621679974924 a6989586621679974925 a6989586621679974926 a6989586621679974927 a6989586621679974928 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # | |
data ZipWith6Sym1 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym1 a6989586621679974896 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym1 a6989586621679974896 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679974897 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym1 a6989586621679974896 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679974897 :: [a]) = ZipWith6Sym2 a6989586621679974896 a6989586621679974897 |
data ZipWith6Sym2 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679974896 a6989586621679974897 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym2 a6989586621679974896 a6989586621679974897 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679974898 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym2 a6989586621679974896 a6989586621679974897 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679974898 :: [b]) = ZipWith6Sym3 a6989586621679974896 a6989586621679974897 a6989586621679974898 |
data ZipWith6Sym3 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g])))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679974896 a6989586621679974897 a6989586621679974898 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym3 a6989586621679974896 a6989586621679974897 a6989586621679974898 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679974899 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym3 a6989586621679974896 a6989586621679974897 a6989586621679974898 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679974899 :: [c]) = ZipWith6Sym4 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 |
data ZipWith6Sym4 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> [g]))) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym4 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679974900 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym4 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679974900 :: [d]) = ZipWith6Sym5 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 |
data ZipWith6Sym5 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (f1 :: TyFun [e] ([f] ~> [g])) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 :: TyFun [e] ([f] ~> [g]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym5 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679974901 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym5 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679974901 :: [e]) = ZipWith6Sym6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 |
data ZipWith6Sym6 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (a6989586621679974901 :: [e]) (g1 :: TyFun [f] [g]) Source #
Instances
SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 :: TyFun [f] [g] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith6Sym6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 :: TyFun [f] [g] -> Type) (a6989586621679974902 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith6Sym6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 :: TyFun [f] [g] -> Type) (a6989586621679974902 :: [f]) = ZipWith6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 a6989586621679974902 |
type family ZipWith6Sym7 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (a6989586621679974901 :: [e]) (a6989586621679974902 :: [f]) :: [g] where ... Source #
ZipWith6Sym7 (a6989586621679974896 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) (a6989586621679974897 :: [a]) (a6989586621679974898 :: [b]) (a6989586621679974899 :: [c]) (a6989586621679974900 :: [d]) (a6989586621679974901 :: [e]) (a6989586621679974902 :: [f]) = ZipWith6 a6989586621679974896 a6989586621679974897 a6989586621679974898 a6989586621679974899 a6989586621679974900 a6989586621679974901 a6989586621679974902 |
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 suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # | |
Defined in Data.List.Singletons.Internal |
data ZipWith7Sym1 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (b1 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym1 a6989586621679974865 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym1 a6989586621679974865 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679974866 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal |
data ZipWith7Sym2 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (c1 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym2 a6989586621679974865 a6989586621679974866 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym2 a6989586621679974865 a6989586621679974866 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679974867 :: [b]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym2 a6989586621679974865 a6989586621679974866 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679974867 :: [b]) = ZipWith7Sym3 a6989586621679974865 a6989586621679974866 a6989586621679974867 |
data ZipWith7Sym3 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (d1 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym3 a6989586621679974865 a6989586621679974866 a6989586621679974867 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym3 a6989586621679974865 a6989586621679974866 a6989586621679974867 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679974868 :: [c]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym3 a6989586621679974865 a6989586621679974866 a6989586621679974867 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679974868 :: [c]) = ZipWith7Sym4 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 |
data ZipWith7Sym4 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (e1 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h])))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym4 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym4 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679974869 :: [d]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym4 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679974869 :: [d]) = ZipWith7Sym5 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 |
data ZipWith7Sym5 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (f1 :: TyFun [e] ([f] ~> ([g] ~> [h]))) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym5 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym5 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679974870 :: [e]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym5 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679974870 :: [e]) = ZipWith7Sym6 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 |
data ZipWith7Sym6 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (g1 :: TyFun [f] ([g] ~> [h])) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 :: TyFun [f] ([g] ~> [h]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym6 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679974871 :: [f]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym6 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679974871 :: [f]) = ZipWith7Sym7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 |
data ZipWith7Sym7 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (a6989586621679974871 :: [f]) (h1 :: TyFun [g] [h]) Source #
Instances
SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 :: TyFun [g] [h] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (ZipWith7Sym7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 :: TyFun [g] [h] -> Type) (a6989586621679974872 :: [g]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (ZipWith7Sym7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 :: TyFun [g] [h] -> Type) (a6989586621679974872 :: [g]) = ZipWith7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 a6989586621679974872 |
type family ZipWith7Sym8 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (a6989586621679974871 :: [f]) (a6989586621679974872 :: [g]) :: [h] where ... Source #
ZipWith7Sym8 (a6989586621679974865 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) (a6989586621679974866 :: [a]) (a6989586621679974867 :: [b]) (a6989586621679974868 :: [c]) (a6989586621679974869 :: [d]) (a6989586621679974870 :: [e]) (a6989586621679974871 :: [f]) (a6989586621679974872 :: [g]) = ZipWith7 a6989586621679974865 a6989586621679974866 a6989586621679974867 a6989586621679974868 a6989586621679974869 a6989586621679974870 a6989586621679974871 a6989586621679974872 |
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 suppressUnusedWarnings :: () # | |
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679824574 :: [(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 suppressUnusedWarnings :: () # | |
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679824556 :: [(a, b, c)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679824556 :: [(a, b, c)]) = Unzip3 a6989586621679824556 |
type family Unzip3Sym1 (a6989586621679824556 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #
Unzip3Sym1 (a6989586621679824556 :: [(a, b, c)]) = Unzip3 a6989586621679824556 |
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 suppressUnusedWarnings :: () # | |
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679824536 :: [(a, b, c, d)]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679824536 :: [(a, b, c, d)]) = Unzip4 a6989586621679824536 |
type family Unzip4Sym1 (a6989586621679824536 :: [(a, b, c, d)]) :: ([a], [b], [c], [d]) where ... Source #
Unzip4Sym1 (a6989586621679824536 :: [(a, b, c, d)]) = Unzip4 a6989586621679824536 |
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 suppressUnusedWarnings :: () # | |
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679824514 :: [(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) (a6989586621679824514 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679824514 |
type family Unzip5Sym1 (a6989586621679824514 :: [(a, b, c, d, e)]) :: ([a], [b], [c], [d], [e]) where ... Source #
Unzip5Sym1 (a6989586621679824514 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679824514 |
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 suppressUnusedWarnings :: () # | |
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679824490 :: [(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) (a6989586621679824490 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679824490 |
type family Unzip6Sym1 (a6989586621679824490 :: [(a, b, c, d, e, f)]) :: ([a], [b], [c], [d], [e], [f]) where ... Source #
Unzip6Sym1 (a6989586621679824490 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679824490 |
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 suppressUnusedWarnings :: () # | |
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679824464 :: [(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) (a6989586621679824464 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679824464 |
type family Unzip7Sym1 (a6989586621679824464 :: [(a, b, c, d, e, f, g)]) :: ([a], [b], [c], [d], [e], [f], [g]) where ... Source #
Unzip7Sym1 (a6989586621679824464 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679824464 |
data UnlinesSym0 (a :: TyFun [Symbol] Symbol) Source #
Instances
SingI UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing UnlinesSym0 # | |
SuppressUnusedWarnings UnlinesSym0 Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply UnlinesSym0 (a6989586621679824459 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal |
type family UnlinesSym1 (a6989586621679824459 :: [Symbol]) :: Symbol where ... Source #
UnlinesSym1 a6989586621679824459 = Unlines a6989586621679824459 |
data UnwordsSym0 (a :: TyFun [Symbol] Symbol) Source #
Instances
SingI UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal sing :: Sing UnwordsSym0 # | |
SuppressUnusedWarnings UnwordsSym0 Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply UnwordsSym0 (a6989586621679824449 :: [Symbol]) Source # | |
Defined in Data.List.Singletons.Internal |
type family UnwordsSym1 (a6989586621679824449 :: [Symbol]) :: Symbol where ... Source #
UnwordsSym1 a6989586621679824449 = Unwords a6989586621679824449 |
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 suppressUnusedWarnings :: () # | |
type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824443 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824443 :: a) = DeleteSym1 a6989586621679824443 |
data DeleteSym1 (a6989586621679824443 :: a) (b :: TyFun [a] [a]) Source #
Instances
SEq a => SingI1 (DeleteSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (DeleteSym1 d) # | |
SuppressUnusedWarnings (DeleteSym1 a6989586621679824443 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (DeleteSym1 a6989586621679824443 :: TyFun [a] [a] -> Type) (a6989586621679824444 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteSym1 a6989586621679824443 :: TyFun [a] [a] -> Type) (a6989586621679824444 :: [a]) = Delete a6989586621679824443 a6989586621679824444 |
type family DeleteSym2 (a6989586621679824443 :: a) (a6989586621679824444 :: [a]) :: [a] where ... Source #
DeleteSym2 (a6989586621679824443 :: a) (a6989586621679824444 :: [a]) = Delete a6989586621679824443 a6989586621679824444 |
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 suppressUnusedWarnings :: () # | |
type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824432 :: [a]) Source # | |
data (a6989586621679824432 :: [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 ((\\@#@$$) a6989586621679824432 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply ((\\@#@$$) a6989586621679824432 :: TyFun [a] [a] -> Type) (a6989586621679824433 :: [a]) Source # | |
type family (a6989586621679824432 :: [a]) \\@#@$$$ (a6989586621679824433 :: [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 suppressUnusedWarnings :: () # | |
type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679823859 :: [a]) Source # | |
data UnionSym1 (a6989586621679823859 :: [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 a6989586621679823859 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (UnionSym1 a6989586621679823859 :: TyFun [a] [a] -> Type) (a6989586621679823860 :: [a]) Source # | |
type family UnionSym2 (a6989586621679823859 :: [a]) (a6989586621679823860 :: [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 suppressUnusedWarnings :: () # | |
type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824250 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824250 :: [a]) = IntersectSym1 a6989586621679824250 |
data IntersectSym1 (a6989586621679824250 :: [a]) (b :: TyFun [a] [a]) Source #
Instances
SEq a => SingI1 (IntersectSym1 :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IntersectSym1 d) # | |
SuppressUnusedWarnings (IntersectSym1 a6989586621679824250 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IntersectSym1 a6989586621679824250 :: TyFun [a] [a] -> Type) (a6989586621679824251 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectSym1 a6989586621679824250 :: TyFun [a] [a] -> Type) (a6989586621679824251 :: [a]) = Intersect a6989586621679824250 a6989586621679824251 |
type family IntersectSym2 (a6989586621679824250 :: [a]) (a6989586621679824251 :: [a]) :: [a] where ... Source #
IntersectSym2 (a6989586621679824250 :: [a]) (a6989586621679824251 :: [a]) = Intersect a6989586621679824250 a6989586621679824251 |
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 suppressUnusedWarnings :: () # | |
type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824052 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824052 :: a) = InsertSym1 a6989586621679824052 |
data InsertSym1 (a6989586621679824052 :: a) (b :: TyFun [a] [a]) Source #
Instances
SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (InsertSym1 d) # | |
SuppressUnusedWarnings (InsertSym1 a6989586621679824052 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (InsertSym1 a6989586621679824052 :: TyFun [a] [a] -> Type) (a6989586621679824053 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertSym1 a6989586621679824052 :: TyFun [a] [a] -> Type) (a6989586621679824053 :: [a]) = Insert a6989586621679824052 a6989586621679824053 |
type family InsertSym2 (a6989586621679824052 :: a) (a6989586621679824053 :: [a]) :: [a] where ... Source #
InsertSym2 (a6989586621679824052 :: a) (a6989586621679824053 :: [a]) = Insert a6989586621679824052 a6989586621679824053 |
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 suppressUnusedWarnings :: () # | |
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679823887 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621679823887 :: 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 a6989586621679823887 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # | |
type Apply (NubBySym1 a6989586621679823887 :: TyFun [a] [a] -> Type) (a6989586621679823888 :: [a]) Source # | |
type family NubBySym2 (a6989586621679823887 :: a ~> (a ~> Bool)) (a6989586621679823888 :: [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 suppressUnusedWarnings :: () # | |
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679824413 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal |
data DeleteBySym1 (a6989586621679824413 :: 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 sing :: Sing (DeleteBySym1 d) # | |
SuppressUnusedWarnings (DeleteBySym1 a6989586621679824413 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (DeleteBySym1 :: (a ~> (a ~> Bool)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (DeleteBySym1 a6989586621679824413 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824414 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym1 a6989586621679824413 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824414 :: a) = DeleteBySym2 a6989586621679824413 a6989586621679824414 |
data DeleteBySym2 (a6989586621679824413 :: a ~> (a ~> Bool)) (a6989586621679824414 :: a) (c :: TyFun [a] [a]) Source #
Instances
SingI d => SingI1 (DeleteBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (DeleteBySym2 d1 d2) # | |
SuppressUnusedWarnings (DeleteBySym2 a6989586621679824413 a6989586621679824414 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (DeleteBySym2 a6989586621679824413 a6989586621679824414 :: TyFun [a] [a] -> Type) (a6989586621679824415 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteBySym2 a6989586621679824413 a6989586621679824414 :: TyFun [a] [a] -> Type) (a6989586621679824415 :: [a]) = DeleteBy a6989586621679824413 a6989586621679824414 a6989586621679824415 |
type family DeleteBySym3 (a6989586621679824413 :: a ~> (a ~> Bool)) (a6989586621679824414 :: a) (a6989586621679824415 :: [a]) :: [a] where ... Source #
DeleteBySym3 (a6989586621679824413 :: a ~> (a ~> Bool)) (a6989586621679824414 :: a) (a6989586621679824415 :: [a]) = DeleteBy a6989586621679824413 a6989586621679824414 a6989586621679824415 |
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 suppressUnusedWarnings :: () # | |
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679824403 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal |
data DeleteFirstsBySym1 (a6989586621679824403 :: 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 sing :: Sing (DeleteFirstsBySym1 d) # | |
SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679824403 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (DeleteFirstsBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (DeleteFirstsBySym1 a6989586621679824403 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824404 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym1 a6989586621679824403 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824404 :: [a]) = DeleteFirstsBySym2 a6989586621679824403 a6989586621679824404 |
data DeleteFirstsBySym2 (a6989586621679824403 :: a ~> (a ~> Bool)) (a6989586621679824404 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
SingI d => SingI1 (DeleteFirstsBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (DeleteFirstsBySym2 d1 d2) # | |
SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679824403 a6989586621679824404 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (DeleteFirstsBySym2 a6989586621679824403 a6989586621679824404 :: TyFun [a] [a] -> Type) (a6989586621679824405 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (DeleteFirstsBySym2 a6989586621679824403 a6989586621679824404 :: TyFun [a] [a] -> Type) (a6989586621679824405 :: [a]) = DeleteFirstsBy a6989586621679824403 a6989586621679824404 a6989586621679824405 |
type family DeleteFirstsBySym3 (a6989586621679824403 :: a ~> (a ~> Bool)) (a6989586621679824404 :: [a]) (a6989586621679824405 :: [a]) :: [a] where ... Source #
DeleteFirstsBySym3 (a6989586621679824403 :: a ~> (a ~> Bool)) (a6989586621679824404 :: [a]) (a6989586621679824405 :: [a]) = DeleteFirstsBy a6989586621679824403 a6989586621679824404 a6989586621679824405 |
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 suppressUnusedWarnings :: () # | |
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679823867 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal |
data UnionBySym1 (a6989586621679823867 :: 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 sing :: Sing (UnionBySym1 d) # | |
SuppressUnusedWarnings (UnionBySym1 a6989586621679823867 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (UnionBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (UnionBySym1 a6989586621679823867 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679823868 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym1 a6989586621679823867 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679823868 :: [a]) = UnionBySym2 a6989586621679823867 a6989586621679823868 |
data UnionBySym2 (a6989586621679823867 :: a ~> (a ~> Bool)) (a6989586621679823868 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
SingI d => SingI1 (UnionBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (UnionBySym2 d1 d2) # | |
SuppressUnusedWarnings (UnionBySym2 a6989586621679823867 a6989586621679823868 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (UnionBySym2 a6989586621679823867 a6989586621679823868 :: TyFun [a] [a] -> Type) (a6989586621679823869 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (UnionBySym2 a6989586621679823867 a6989586621679823868 :: TyFun [a] [a] -> Type) (a6989586621679823869 :: [a]) = UnionBy a6989586621679823867 a6989586621679823868 a6989586621679823869 |
type family UnionBySym3 (a6989586621679823867 :: a ~> (a ~> Bool)) (a6989586621679823868 :: [a]) (a6989586621679823869 :: [a]) :: [a] where ... Source #
UnionBySym3 (a6989586621679823867 :: a ~> (a ~> Bool)) (a6989586621679823868 :: [a]) (a6989586621679823869 :: [a]) = UnionBy a6989586621679823867 a6989586621679823868 a6989586621679823869 |
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 suppressUnusedWarnings :: () # | |
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679824228 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal |
data IntersectBySym1 (a6989586621679824228 :: 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 sing :: Sing (IntersectBySym1 d) # | |
SuppressUnusedWarnings (IntersectBySym1 a6989586621679824228 :: TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (IntersectBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (IntersectBySym1 a6989586621679824228 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824229 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym1 a6989586621679824228 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679824229 :: [a]) = IntersectBySym2 a6989586621679824228 a6989586621679824229 |
data IntersectBySym2 (a6989586621679824228 :: a ~> (a ~> Bool)) (a6989586621679824229 :: [a]) (c :: TyFun [a] [a]) Source #
Instances
SingI d => SingI1 (IntersectBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (IntersectBySym2 d1 d2) # | |
SuppressUnusedWarnings (IntersectBySym2 a6989586621679824228 a6989586621679824229 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (IntersectBySym2 a6989586621679824228 a6989586621679824229 :: TyFun [a] [a] -> Type) (a6989586621679824230 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (IntersectBySym2 a6989586621679824228 a6989586621679824229 :: TyFun [a] [a] -> Type) (a6989586621679824230 :: [a]) = IntersectBy a6989586621679824228 a6989586621679824229 a6989586621679824230 |
type family IntersectBySym3 (a6989586621679824228 :: a ~> (a ~> Bool)) (a6989586621679824229 :: [a]) (a6989586621679824230 :: [a]) :: [a] where ... Source #
IntersectBySym3 (a6989586621679824228 :: a ~> (a ~> Bool)) (a6989586621679824229 :: [a]) (a6989586621679824230 :: [a]) = IntersectBy a6989586621679824228 a6989586621679824229 a6989586621679824230 |
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 suppressUnusedWarnings :: () # | |
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679824020 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.Singletons.Internal |
data GroupBySym1 (a6989586621679824020 :: 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 sing :: Sing (GroupBySym1 d) # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621679824020 :: TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [[a]] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (GroupBySym1 a6989586621679824020 :: TyFun [a] [[a]] -> Type) (a6989586621679824021 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GroupBySym1 a6989586621679824020 :: TyFun [a] [[a]] -> Type) (a6989586621679824021 :: [a]) = GroupBy a6989586621679824020 a6989586621679824021 |
type family GroupBySym2 (a6989586621679824020 :: a ~> (a ~> Bool)) (a6989586621679824021 :: [a]) :: [[a]] where ... Source #
GroupBySym2 (a6989586621679824020 :: a ~> (a ~> Bool)) (a6989586621679824021 :: [a]) = GroupBy a6989586621679824020 a6989586621679824021 |
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 suppressUnusedWarnings :: () # | |
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679824391 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal |
data SortBySym1 (a6989586621679824391 :: 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 sing :: Sing (SortBySym1 d) # | |
SuppressUnusedWarnings (SortBySym1 a6989586621679824391 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (SortBySym1 a6989586621679824391 :: TyFun [a] [a] -> Type) (a6989586621679824392 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (SortBySym1 a6989586621679824391 :: TyFun [a] [a] -> Type) (a6989586621679824392 :: [a]) = SortBy a6989586621679824391 a6989586621679824392 |
type family SortBySym2 (a6989586621679824391 :: a ~> (a ~> Ordering)) (a6989586621679824392 :: [a]) :: [a] where ... Source #
SortBySym2 (a6989586621679824391 :: a ~> (a ~> Ordering)) (a6989586621679824392 :: [a]) = SortBy a6989586621679824391 a6989586621679824392 |
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 suppressUnusedWarnings :: () # | |
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679824371 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.Singletons.Internal |
data InsertBySym1 (a6989586621679824371 :: 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 sing :: Sing (InsertBySym1 d) # | |
SuppressUnusedWarnings (InsertBySym1 a6989586621679824371 :: TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
SingI1 (InsertBySym1 :: (a ~> (a ~> Ordering)) -> TyFun a ([a] ~> [a]) -> Type) Source # | |
Defined in Data.List.Singletons.Internal | |
type Apply (InsertBySym1 a6989586621679824371 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824372 :: a) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym1 a6989586621679824371 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679824372 :: a) = InsertBySym2 a6989586621679824371 a6989586621679824372 |
data InsertBySym2 (a6989586621679824371 :: a ~> (a ~> Ordering)) (a6989586621679824372 :: a) (c :: TyFun [a] [a]) Source #
Instances
SingI d => SingI1 (InsertBySym2 d :: a -> TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal 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 sing :: Sing (InsertBySym2 d1 d2) # | |
SuppressUnusedWarnings (InsertBySym2 a6989586621679824371 a6989586621679824372 :: TyFun [a] [a] -> Type) Source # | |
Defined in Data.List.Singletons.Internal suppressUnusedWarnings :: () # | |
type Apply (InsertBySym2 a6989586621679824371 a6989586621679824372 :: TyFun [a] [a] -> Type) (a6989586621679824373 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (InsertBySym2 a6989586621679824371 a6989586621679824372 :: TyFun [a] [a] -> Type) (a6989586621679824373 :: [a]) = InsertBy a6989586621679824371 a6989586621679824372 a6989586621679824373 |
type family InsertBySym3 (a6989586621679824371 :: a ~> (a ~> Ordering)) (a6989586621679824372 :: a) (a6989586621679824373 :: [a]) :: [a] where ... Source #
InsertBySym3 (a6989586621679824371 :: a ~> (a ~> Ordering)) (a6989586621679824372 :: a) (a6989586621679824373 :: [a]) = InsertBy a6989586621679824371 a6989586621679824372 a6989586621679824373 |
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 suppressUnusedWarnings :: () # | |
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680404104 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons |
data MaximumBySym1 (a6989586621680404104 :: 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 a6989586621680404104 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MaximumBySym1 a6989586621680404104 :: TyFun (t a) a -> Type) (a6989586621680404105 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MaximumBySym1 a6989586621680404104 :: TyFun (t a) a -> Type) (a6989586621680404105 :: t a) = MaximumBy a6989586621680404104 a6989586621680404105 |
type family MaximumBySym2 (a6989586621680404104 :: a ~> (a ~> Ordering)) (a6989586621680404105 :: t a) :: a where ... Source #
MaximumBySym2 (a6989586621680404104 :: a ~> (a ~> Ordering)) (a6989586621680404105 :: t a) = MaximumBy a6989586621680404104 a6989586621680404105 |
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 suppressUnusedWarnings :: () # | |
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680404084 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.Foldable.Singletons |
data MinimumBySym1 (a6989586621680404084 :: 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 a6989586621680404084 :: TyFun (t a) a -> Type) Source # | |
Defined in Data.Foldable.Singletons suppressUnusedWarnings :: () # | |
type Apply (MinimumBySym1 a6989586621680404084 :: TyFun (t a) a -> Type) (a6989586621680404085 :: t a) Source # | |
Defined in Data.Foldable.Singletons type Apply (MinimumBySym1 a6989586621680404084 :: TyFun (t a) a -> Type) (a6989586621680404085 :: t a) = MinimumBy a6989586621680404084 a6989586621680404085 |
type family MinimumBySym2 (a6989586621680404084 :: a ~> (a ~> Ordering)) (a6989586621680404085 :: t a) :: a where ... Source #
MinimumBySym2 (a6989586621680404084 :: a ~> (a ~> Ordering)) (a6989586621680404085 :: t a) = MinimumBy a6989586621680404084 a6989586621680404085 |
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 suppressUnusedWarnings :: () # | |
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679823850 :: [a]) Source # | |
Defined in Data.List.Singletons.Internal type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679823850 :: [a]) = GenericLength a6989586621679823850 :: k2 |
type family GenericLengthSym1 (a6989586621679823850 :: [a]) :: i where ... Source #
GenericLengthSym1 (a6989586621679823850 :: [a]) = GenericLength a6989586621679823850 :: i |