Copyright | (C) 2016 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | GHC2021 |
Data.List.NonEmpty.Singletons
Description
Defines functions and datatypes relating to the singleton for NonEmpty
,
including singled versions of all the definitions in Data.List.NonEmpty
.
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.NonEmpty
. 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 SNonEmpty (a1 :: NonEmpty a) where
- type family Map (a1 :: a ~> b) (a2 :: NonEmpty a) :: NonEmpty b where ...
- sMap :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Map t1 t2)
- type family Intersperse (a1 :: a) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sIntersperse :: forall a (t1 :: a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Intersperse t1 t2)
- type family Scanl (a1 :: b ~> (a ~> b)) (a2 :: b) (a3 :: [a]) :: NonEmpty b where ...
- sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanl t1 t2 t3)
- type family Scanr (a1 :: a ~> (b ~> b)) (a2 :: b) (a3 :: [a]) :: NonEmpty b where ...
- sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanr t1 t2 t3)
- type family Scanl1 (a1 :: a ~> (a ~> a)) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sScanl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Scanl1 t1 t2)
- type family Scanr1 (a1 :: a ~> (a ~> a)) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Scanr1 t1 t2)
- type family Transpose (a1 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- sTranspose :: forall a (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Transpose t)
- type family SortBy (a1 :: a ~> (a ~> Ordering)) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sSortBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (SortBy t1 t2)
- type family SortWith (a1 :: a ~> o) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sSortWith :: forall a o (t1 :: a ~> o) (t2 :: NonEmpty a). SOrd o => Sing t1 -> Sing t2 -> Sing (SortWith t1 t2)
- type family Length (a1 :: NonEmpty a) :: Natural where ...
- sLength :: forall a (t :: NonEmpty a). Sing t -> Sing (Length t)
- type family Head (a1 :: NonEmpty a) :: a where ...
- sHead :: forall a (t :: NonEmpty a). Sing t -> Sing (Head t)
- type family Tail (a1 :: NonEmpty a) :: [a] where ...
- sTail :: forall a (t :: NonEmpty a). Sing t -> Sing (Tail t)
- type family Last (a1 :: NonEmpty a) :: a where ...
- sLast :: forall a (t :: NonEmpty a). Sing t -> Sing (Last t)
- type family Init (a1 :: NonEmpty a) :: [a] where ...
- sInit :: forall a (t :: NonEmpty a). Sing t -> Sing (Init t)
- type family (a1 :: a) <| (a2 :: NonEmpty a) :: NonEmpty a where ...
- (%<|) :: forall a (t1 :: a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 <| t2)
- type family Cons (a1 :: a) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sCons :: forall a (t1 :: a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Cons t1 t2)
- type family Uncons (a1 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Uncons t)
- type family Unfoldr (a1 :: a ~> (b, Maybe a)) (a2 :: a) :: NonEmpty b where ...
- sUnfoldr :: forall a b (t1 :: a ~> (b, Maybe a)) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Unfoldr t1 t2)
- type family Sort (a1 :: NonEmpty a) :: NonEmpty a where ...
- sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Sort t)
- type family Reverse (a1 :: NonEmpty a) :: NonEmpty a where ...
- sReverse :: forall a (t :: NonEmpty a). Sing t -> Sing (Reverse t)
- type family Inits (a1 :: [a]) :: NonEmpty [a] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Inits t)
- type family Tails (a1 :: [a]) :: NonEmpty [a] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Tails t)
- type family Unfold (a1 :: a ~> (b, Maybe a)) (a2 :: a) :: NonEmpty b where ...
- sUnfold :: forall a b (t1 :: a ~> (b, Maybe a)) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Unfold t1 t2)
- type family Insert (a1 :: a) (a2 :: [a]) :: NonEmpty a where ...
- sInsert :: forall a (t1 :: a) (t2 :: [a]). SOrd a => Sing t1 -> Sing t2 -> Sing (Insert t1 t2)
- type family Take (a1 :: Natural) (a2 :: NonEmpty a) :: [a] where ...
- sTake :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Take t1 t2)
- type family Drop (a1 :: Natural) (a2 :: NonEmpty a) :: [a] where ...
- sDrop :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Drop t1 t2)
- type family SplitAt (a1 :: Natural) (a2 :: NonEmpty a) :: ([a], [a]) where ...
- sSplitAt :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (SplitAt t1 t2)
- type family TakeWhile (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ...
- sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (TakeWhile t1 t2)
- type family DropWhile (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ...
- sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (DropWhile t1 t2)
- type family Span (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: ([a], [a]) where ...
- sSpan :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Span t1 t2)
- type family Break (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: ([a], [a]) where ...
- sBreak :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Break t1 t2)
- type family Filter (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ...
- sFilter :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Filter t1 t2)
- type family Partition (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: ([a], [a]) where ...
- sPartition :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Partition t1 t2)
- type family Group (a1 :: [a]) :: [NonEmpty a] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Group t)
- type family GroupBy (a1 :: a ~> (a ~> Bool)) (a2 :: [a]) :: [NonEmpty a] where ...
- sGroupBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (GroupBy t1 t2)
- type family GroupWith (a1 :: a ~> b) (a2 :: [a]) :: [NonEmpty a] where ...
- sGroupWith :: forall a b (t1 :: a ~> b) (t2 :: [a]). SEq b => Sing t1 -> Sing t2 -> Sing (GroupWith t1 t2)
- type family GroupAllWith (a1 :: a ~> b) (a2 :: [a]) :: [NonEmpty a] where ...
- sGroupAllWith :: forall a b (t1 :: a ~> b) (t2 :: [a]). SOrd b => Sing t1 -> Sing t2 -> Sing (GroupAllWith t1 t2)
- type family Group1 (a1 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroup1 :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Group1 t)
- type family GroupBy1 (a1 :: a ~> (a ~> Bool)) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupBy1 :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (GroupBy1 t1 t2)
- type family GroupWith1 (a1 :: a ~> b) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupWith1 :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). SEq b => Sing t1 -> Sing t2 -> Sing (GroupWith1 t1 t2)
- type family GroupAllWith1 (a1 :: a ~> b) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupAllWith1 :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). SOrd b => Sing t1 -> Sing t2 -> Sing (GroupAllWith1 t1 t2)
- type family IsPrefixOf (a1 :: [a]) (a2 :: NonEmpty a) :: Bool where ...
- sIsPrefixOf :: forall a (t1 :: [a]) (t2 :: NonEmpty a). SEq a => Sing t1 -> Sing t2 -> Sing (IsPrefixOf t1 t2)
- type family Nub (a1 :: NonEmpty a) :: NonEmpty a where ...
- sNub :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Nub t)
- type family NubBy (a1 :: a ~> (a ~> Bool)) (a2 :: NonEmpty a) :: NonEmpty a where ...
- sNubBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (NubBy t1 t2)
- type family (a1 :: NonEmpty a) !! (a2 :: Natural) :: a where ...
- (%!!) :: forall a (t1 :: NonEmpty a) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 !! t2)
- type family Zip (a1 :: NonEmpty a) (a2 :: NonEmpty b) :: NonEmpty (a, b) where ...
- sZip :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Zip t1 t2)
- type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: NonEmpty a) (a3 :: NonEmpty b) :: NonEmpty c where ...
- sZipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ZipWith t1 t2 t3)
- type family Unzip (a1 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Unzip t)
- type family FromList (a1 :: [a]) :: NonEmpty a where ...
- sFromList :: forall a (t :: [a]). Sing t -> Sing (FromList t)
- type family ToList (a1 :: NonEmpty a) :: [a] where ...
- sToList :: forall a (t :: NonEmpty a). Sing t -> Sing (ToList t)
- type family NonEmpty_ (a1 :: [a]) :: Maybe (NonEmpty a) where ...
- sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (NonEmpty_ t)
- type family Xor (a :: NonEmpty Bool) :: Bool where ...
- sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Xor t)
- data (:|@#@$) (a1 :: TyFun a ([a] ~> NonEmpty a))
- data (a6989586621679050362 :: a) :|@#@$$ (b :: TyFun [a] (NonEmpty a))
- type family (a6989586621679050362 :: a) :|@#@$$$ (a6989586621679050363 :: [a]) :: NonEmpty a where ...
- data MapSym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b))
- data MapSym1 (a6989586621680287251 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty b))
- type family MapSym2 (a6989586621680287251 :: a ~> b) (a6989586621680287252 :: NonEmpty a) :: NonEmpty b where ...
- data IntersperseSym0 (a1 :: TyFun a (NonEmpty a ~> NonEmpty a))
- data IntersperseSym1 (a6989586621680287177 :: a) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family IntersperseSym2 (a6989586621680287177 :: a) (a6989586621680287178 :: NonEmpty a) :: NonEmpty a where ...
- data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)))
- data ScanlSym1 (a6989586621680287221 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> NonEmpty b))
- data ScanlSym2 (a6989586621680287221 :: b ~> (a ~> b)) (a6989586621680287222 :: b) (c :: TyFun [a] (NonEmpty b))
- type family ScanlSym3 (a6989586621680287221 :: b ~> (a ~> b)) (a6989586621680287222 :: b) (a6989586621680287223 :: [a]) :: NonEmpty b where ...
- data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)))
- data ScanrSym1 (a6989586621680287209 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> NonEmpty b))
- data ScanrSym2 (a6989586621680287209 :: a ~> (b ~> b)) (a6989586621680287210 :: b) (c :: TyFun [a] (NonEmpty b))
- type family ScanrSym3 (a6989586621680287209 :: a ~> (b ~> b)) (a6989586621680287210 :: b) (a6989586621680287211 :: [a]) :: NonEmpty b where ...
- data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a))
- data Scanl1Sym1 (a6989586621680287198 :: a ~> (a ~> a)) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family Scanl1Sym2 (a6989586621680287198 :: a ~> (a ~> a)) (a6989586621680287199 :: NonEmpty a) :: NonEmpty a where ...
- data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a))
- data Scanr1Sym1 (a6989586621680287190 :: a ~> (a ~> a)) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family Scanr1Sym2 (a6989586621680287190 :: a ~> (a ~> a)) (a6989586621680287191 :: NonEmpty a) :: NonEmpty a where ...
- data TransposeSym0 (a1 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)))
- type family TransposeSym1 (a6989586621680286864 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- data SortBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a))
- data SortBySym1 (a6989586621680286856 :: a ~> (a ~> Ordering)) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family SortBySym2 (a6989586621680286856 :: a ~> (a ~> Ordering)) (a6989586621680286857 :: NonEmpty a) :: NonEmpty a where ...
- data SortWithSym0 (a1 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a))
- data SortWithSym1 (a6989586621680286847 :: a ~> o) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family SortWithSym2 (a6989586621680286847 :: a ~> o) (a6989586621680286848 :: NonEmpty a) :: NonEmpty a where ...
- data LengthSym0 (a1 :: TyFun (NonEmpty a) Natural)
- type family LengthSym1 (a6989586621680287381 :: NonEmpty a) :: Natural where ...
- data HeadSym0 (a1 :: TyFun (NonEmpty a) a)
- type family HeadSym1 (a6989586621680287316 :: NonEmpty a) :: a where ...
- data TailSym0 (a1 :: TyFun (NonEmpty a) [a])
- type family TailSym1 (a6989586621680287312 :: NonEmpty a) :: [a] where ...
- data LastSym0 (a1 :: TyFun (NonEmpty a) a)
- type family LastSym1 (a6989586621680287307 :: NonEmpty a) :: a where ...
- data InitSym0 (a1 :: TyFun (NonEmpty a) [a])
- type family InitSym1 (a6989586621680287302 :: NonEmpty a) :: [a] where ...
- data (<|@#@$) (a1 :: TyFun a (NonEmpty a ~> NonEmpty a))
- data (a6989586621680287295 :: a) <|@#@$$ (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family (a6989586621680287295 :: a) <|@#@$$$ (a6989586621680287296 :: NonEmpty a) :: NonEmpty a where ...
- data ConsSym0 (a1 :: TyFun a (NonEmpty a ~> NonEmpty a))
- data ConsSym1 (a6989586621680287288 :: a) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family ConsSym2 (a6989586621680287288 :: a) (a6989586621680287289 :: NonEmpty a) :: NonEmpty a where ...
- data UnconsSym0 (a1 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)))
- type family UnconsSym1 (a6989586621680287345 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- data UnfoldrSym0 (a1 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b))
- data UnfoldrSym1 (a6989586621680287321 :: a ~> (b, Maybe a)) (b1 :: TyFun a (NonEmpty b))
- type family UnfoldrSym2 (a6989586621680287321 :: a ~> (b, Maybe a)) (a6989586621680287322 :: a) :: NonEmpty b where ...
- data SortSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a))
- type family SortSym1 (a6989586621680287279 :: NonEmpty a) :: NonEmpty a where ...
- data ReverseSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a))
- type family ReverseSym1 (a6989586621680287172 :: NonEmpty a) :: NonEmpty a where ...
- data InitsSym0 (a1 :: TyFun [a] (NonEmpty [a]))
- type family InitsSym1 (a6989586621680287246 :: [a]) :: NonEmpty [a] where ...
- data TailsSym0 (a1 :: TyFun [a] (NonEmpty [a]))
- type family TailsSym1 (a6989586621680287240 :: [a]) :: NonEmpty [a] where ...
- data UnfoldSym0 (a1 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b))
- data UnfoldSym1 (a6989586621680287356 :: a ~> (b, Maybe a)) (b1 :: TyFun a (NonEmpty b))
- data InsertSym0 (a1 :: TyFun a ([a] ~> NonEmpty a))
- data InsertSym1 (a6989586621680287232 :: a) (b :: TyFun [a] (NonEmpty a))
- type family InsertSym2 (a6989586621680287232 :: a) (a6989586621680287233 :: [a]) :: NonEmpty a where ...
- data TakeSym0 (a1 :: TyFun Natural (NonEmpty a ~> [a]))
- data TakeSym1 (a6989586621680287164 :: Natural) (b :: TyFun (NonEmpty a) [a])
- type family TakeSym2 (a6989586621680287164 :: Natural) (a6989586621680287165 :: NonEmpty a) :: [a] where ...
- data DropSym0 (a1 :: TyFun Natural (NonEmpty a ~> [a]))
- data DropSym1 (a6989586621680287155 :: Natural) (b :: TyFun (NonEmpty a) [a])
- type family DropSym2 (a6989586621680287155 :: Natural) (a6989586621680287156 :: NonEmpty a) :: [a] where ...
- data SplitAtSym0 (a1 :: TyFun Natural (NonEmpty a ~> ([a], [a])))
- data SplitAtSym1 (a6989586621680287146 :: Natural) (b :: TyFun (NonEmpty a) ([a], [a]))
- type family SplitAtSym2 (a6989586621680287146 :: Natural) (a6989586621680287147 :: NonEmpty a) :: ([a], [a]) where ...
- data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]))
- data TakeWhileSym1 (a6989586621680287137 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a])
- type family TakeWhileSym2 (a6989586621680287137 :: a ~> Bool) (a6989586621680287138 :: NonEmpty a) :: [a] where ...
- data DropWhileSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]))
- data DropWhileSym1 (a6989586621680287128 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a])
- type family DropWhileSym2 (a6989586621680287128 :: a ~> Bool) (a6989586621680287129 :: NonEmpty a) :: [a] where ...
- data SpanSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])))
- data SpanSym1 (a6989586621680287119 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a]))
- type family SpanSym2 (a6989586621680287119 :: a ~> Bool) (a6989586621680287120 :: NonEmpty a) :: ([a], [a]) where ...
- data BreakSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])))
- data BreakSym1 (a6989586621680287110 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a]))
- type family BreakSym2 (a6989586621680287110 :: a ~> Bool) (a6989586621680287111 :: NonEmpty a) :: ([a], [a]) where ...
- data FilterSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]))
- data FilterSym1 (a6989586621680287101 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a])
- type family FilterSym2 (a6989586621680287101 :: a ~> Bool) (a6989586621680287102 :: NonEmpty a) :: [a] where ...
- data PartitionSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])))
- data PartitionSym1 (a6989586621680287092 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a]))
- type family PartitionSym2 (a6989586621680287092 :: a ~> Bool) (a6989586621680287093 :: NonEmpty a) :: ([a], [a]) where ...
- data GroupSym0 (a1 :: TyFun [a] [NonEmpty a])
- type family GroupSym1 (a6989586621680287085 :: [a]) :: [NonEmpty a] where ...
- data GroupBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]))
- data GroupBySym1 (a6989586621680287048 :: a ~> (a ~> Bool)) (b :: TyFun [a] [NonEmpty a])
- type family GroupBySym2 (a6989586621680287048 :: a ~> (a ~> Bool)) (a6989586621680287049 :: [a]) :: [NonEmpty a] where ...
- data GroupWithSym0 (a1 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]))
- data GroupWithSym1 (a6989586621680287039 :: a ~> b) (b1 :: TyFun [a] [NonEmpty a])
- type family GroupWithSym2 (a6989586621680287039 :: a ~> b) (a6989586621680287040 :: [a]) :: [NonEmpty a] where ...
- data GroupAllWithSym0 (a1 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]))
- data GroupAllWithSym1 (a6989586621680287030 :: a ~> b) (b1 :: TyFun [a] [NonEmpty a])
- type family GroupAllWithSym2 (a6989586621680287030 :: a ~> b) (a6989586621680287031 :: [a]) :: [NonEmpty a] where ...
- data Group1Sym0 (a1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)))
- type family Group1Sym1 (a6989586621680287023 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupBy1Sym0 (a1 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)))
- data GroupBy1Sym1 (a6989586621680286992 :: a ~> (a ~> Bool)) (b :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)))
- type family GroupBy1Sym2 (a6989586621680286992 :: a ~> (a ~> Bool)) (a6989586621680286993 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupWith1Sym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)))
- data GroupWith1Sym1 (a6989586621680286985 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)))
- type family GroupWith1Sym2 (a6989586621680286985 :: a ~> b) (a6989586621680286986 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupAllWith1Sym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)))
- data GroupAllWith1Sym1 (a6989586621680286976 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)))
- type family GroupAllWith1Sym2 (a6989586621680286976 :: a ~> b) (a6989586621680286977 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data IsPrefixOfSym0 (a1 :: TyFun [a] (NonEmpty a ~> Bool))
- data IsPrefixOfSym1 (a6989586621680286965 :: [a]) (b :: TyFun (NonEmpty a) Bool)
- type family IsPrefixOfSym2 (a6989586621680286965 :: [a]) (a6989586621680286966 :: NonEmpty a) :: Bool where ...
- data NubSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a))
- type family NubSym1 (a6989586621680286884 :: NonEmpty a) :: NonEmpty a where ...
- data NubBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a))
- data NubBySym1 (a6989586621680286869 :: a ~> (a ~> Bool)) (b :: TyFun (NonEmpty a) (NonEmpty a))
- type family NubBySym2 (a6989586621680286869 :: a ~> (a ~> Bool)) (a6989586621680286870 :: NonEmpty a) :: NonEmpty a where ...
- data (!!@#@$) (a1 :: TyFun (NonEmpty a) (Natural ~> a))
- data (a6989586621680286938 :: NonEmpty a) !!@#@$$ (b :: TyFun Natural a)
- type family (a6989586621680286938 :: NonEmpty a) !!@#@$$$ (a6989586621680286939 :: Natural) :: a where ...
- data ZipSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)))
- data ZipSym1 (a6989586621680286929 :: NonEmpty a) (b1 :: TyFun (NonEmpty b) (NonEmpty (a, b)))
- type family ZipSym2 (a6989586621680286929 :: NonEmpty a) (a6989586621680286930 :: NonEmpty b) :: NonEmpty (a, b) where ...
- data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)))
- data ZipWithSym1 (a6989586621680286918 :: a ~> (b ~> c)) (b1 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c))
- data ZipWithSym2 (a6989586621680286918 :: a ~> (b ~> c)) (a6989586621680286919 :: NonEmpty a) (c1 :: TyFun (NonEmpty b) (NonEmpty c))
- type family ZipWithSym3 (a6989586621680286918 :: a ~> (b ~> c)) (a6989586621680286919 :: NonEmpty a) (a6989586621680286920 :: NonEmpty b) :: NonEmpty c where ...
- data UnzipSym0 (a1 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b))
- type family UnzipSym1 (a6989586621680286888 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- data FromListSym0 (a1 :: TyFun [a] (NonEmpty a))
- type family FromListSym1 (a6989586621680287272 :: [a]) :: NonEmpty a where ...
- data ToListSym0 (a1 :: TyFun (NonEmpty a) [a])
- type family ToListSym1 (a6989586621680287267 :: NonEmpty a) :: [a] where ...
- data NonEmpty_Sym0 (a1 :: TyFun [a] (Maybe (NonEmpty a)))
- type family NonEmpty_Sym1 (a6989586621680287350 :: [a]) :: Maybe (NonEmpty a) where ...
- data XorSym0 (a :: TyFun (NonEmpty Bool) Bool)
- type family XorSym1 (a6989586621680287370 :: NonEmpty Bool) :: Bool where ...
The NonEmpty
singleton
type family Sing :: k -> Type #
Instances
data SNonEmpty (a1 :: NonEmpty a) where Source #
Constructors
(:%|) :: forall a (n1 :: a) (n2 :: [a]). Sing n1 -> Sing n2 -> SNonEmpty (n1 ':| n2) infixr 5 |
Instances
(SDecide a, SDecide [a]) => TestCoercion (SNonEmpty :: NonEmpty a -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
(SDecide a, SDecide [a]) => TestEquality (SNonEmpty :: NonEmpty a -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
(ShowSing a, ShowSing [a]) => Show (SNonEmpty z) Source # | |
Eq (SNonEmpty z) Source # | |
Non-empty stream transformations
sMap :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Map t1 t2) Source #
type family Intersperse (a1 :: a) (a2 :: NonEmpty a) :: NonEmpty a where ... Source #
sIntersperse :: forall a (t1 :: a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Intersperse t1 t2) Source #
type family Scanl (a1 :: b ~> (a ~> b)) (a2 :: b) (a3 :: [a]) :: NonEmpty b where ... Source #
Equations
Scanl (f :: a1 ~> (a2 ~> a1)) (z :: a1) (a_6989586621680287215 :: [a2]) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a1] ~> NonEmpty a1) (([a2] ~> [a1]) ~> ([a2] ~> NonEmpty a1)) -> Type) (FromListSym0 :: TyFun [a1] (NonEmpty a1) -> Type)) (Apply (Apply (ListscanlSym0 :: TyFun (a1 ~> (a2 ~> a1)) (a1 ~> ([a2] ~> [a1])) -> Type) f) z)) a_6989586621680287215 |
sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanl t1 t2 t3) Source #
type family Scanr (a1 :: a ~> (b ~> b)) (a2 :: b) (a3 :: [a]) :: NonEmpty b where ... Source #
Equations
Scanr (f :: a1 ~> (a2 ~> a2)) (z :: a2) (a_6989586621680287203 :: [a1]) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a2] ~> NonEmpty a2) (([a1] ~> [a2]) ~> ([a1] ~> NonEmpty a2)) -> Type) (FromListSym0 :: TyFun [a2] (NonEmpty a2) -> Type)) (Apply (Apply (ListscanrSym0 :: TyFun (a1 ~> (a2 ~> a2)) (a2 ~> ([a1] ~> [a2])) -> Type) f) z)) a_6989586621680287203 |
sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanr t1 t2 t3) Source #
sScanl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Scanl1 t1 t2) Source #
sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Scanr1 t1 t2) Source #
type family Transpose (a1 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
sSortBy :: forall a (t1 :: a ~> (a ~> Ordering)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (SortBy t1 t2) Source #
type family SortWith (a1 :: a ~> o) (a2 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
SortWith (a_6989586621680286840 :: a1 ~> a2) (a_6989586621680286842 :: NonEmpty a1) = Apply (Apply (Apply (Apply ((.@#@$) :: TyFun ((a1 ~> (a1 ~> Ordering)) ~> (NonEmpty a1 ~> NonEmpty a1)) (((a1 ~> a2) ~> (a1 ~> (a1 ~> Ordering))) ~> ((a1 ~> a2) ~> (NonEmpty a1 ~> NonEmpty a1))) -> Type) (SortBySym0 :: TyFun (a1 ~> (a1 ~> Ordering)) (NonEmpty a1 ~> NonEmpty a1) -> Type)) (ComparingSym0 :: TyFun (a1 ~> a2) (a1 ~> (a1 ~> Ordering)) -> Type)) a_6989586621680286840) a_6989586621680286842 |
sSortWith :: forall a o (t1 :: a ~> o) (t2 :: NonEmpty a). SOrd o => Sing t1 -> Sing t2 -> Sing (SortWith t1 t2) Source #
sUnfoldr :: forall a b (t1 :: a ~> (b, Maybe a)) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Unfoldr t1 t2) Source #
sUnfold :: forall a b (t1 :: a ~> (b, Maybe a)) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Unfold t1 t2) Source #
type family Insert (a1 :: a) (a2 :: [a]) :: NonEmpty a where ... Source #
Equations
Insert (a2 :: a1) (a_6989586621680287227 :: [a1]) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a1] ~> NonEmpty a1) (([a1] ~> [a1]) ~> ([a1] ~> NonEmpty a1)) -> Type) (FromListSym0 :: TyFun [a1] (NonEmpty a1) -> Type)) (Apply (ListinsertSym0 :: TyFun a1 ([a1] ~> [a1]) -> Type) a2)) a_6989586621680287227 |
sInsert :: forall a (t1 :: a) (t2 :: [a]). SOrd a => Sing t1 -> Sing t2 -> Sing (Insert t1 t2) Source #
sTake :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Take t1 t2) Source #
sDrop :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Drop t1 t2) Source #
type family SplitAt (a1 :: Natural) (a2 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
SplitAt n (a_6989586621680287141 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> ([a], [a])) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> ([a], [a]))) -> Type) (Apply (ListsplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) n)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287141 |
sSplitAt :: forall a (t1 :: Natural) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (SplitAt t1 t2) Source #
type family TakeWhile (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ... Source #
Equations
TakeWhile (p :: a ~> Bool) (a_6989586621680287132 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> [a]) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> [a])) -> Type) (Apply (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) p)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287132 |
sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (TakeWhile t1 t2) Source #
type family DropWhile (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ... Source #
Equations
DropWhile (p :: a ~> Bool) (a_6989586621680287123 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> [a]) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> [a])) -> Type) (Apply (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) p)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287123 |
sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (DropWhile t1 t2) Source #
type family Span (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
Span (p :: a ~> Bool) (a_6989586621680287114 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> ([a], [a])) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> ([a], [a]))) -> Type) (Apply (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) p)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287114 |
sSpan :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Span t1 t2) Source #
sBreak :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Break t1 t2) Source #
type family Filter (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: [a] where ... Source #
Equations
Filter (p :: a ~> Bool) (a_6989586621680287096 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> [a]) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> [a])) -> Type) (Apply (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) p)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287096 |
sFilter :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Filter t1 t2) Source #
type family Partition (a1 :: a ~> Bool) (a2 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
Partition (p :: a ~> Bool) (a_6989586621680287087 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> ([a], [a])) ((NonEmpty a ~> [a]) ~> (NonEmpty a ~> ([a], [a]))) -> Type) (Apply (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) p)) (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type)) a_6989586621680287087 |
sPartition :: forall a (t1 :: a ~> Bool) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Partition t1 t2) Source #
sGroupBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (GroupBy t1 t2) Source #
type family GroupWith (a1 :: a ~> b) (a2 :: [a]) :: [NonEmpty a] where ... Source #
Equations
GroupWith (f :: a ~> b) (a_6989586621680287034 :: [a]) = Apply (Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (Apply (Apply (OnSym0 :: TyFun (b ~> (b ~> Bool)) ((a ~> b) ~> (a ~> (a ~> Bool))) -> Type) ((==@#@$) :: TyFun b (b ~> Bool) -> Type)) f)) a_6989586621680287034 |
sGroupWith :: forall a b (t1 :: a ~> b) (t2 :: [a]). SEq b => Sing t1 -> Sing t2 -> Sing (GroupWith t1 t2) Source #
type family GroupAllWith (a1 :: a ~> b) (a2 :: [a]) :: [NonEmpty a] where ... Source #
Equations
GroupAllWith (f :: a ~> b) (a_6989586621680287025 :: [a]) = Apply (Apply (Apply ((.@#@$) :: TyFun ([a] ~> [NonEmpty a]) (([a] ~> [a]) ~> ([a] ~> [NonEmpty a])) -> Type) (Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) f)) (Apply (ListsortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (Apply (Apply (OnSym0 :: TyFun (b ~> (b ~> Ordering)) ((a ~> b) ~> (a ~> (a ~> Ordering))) -> Type) (CompareSym0 :: TyFun b (b ~> Ordering) -> Type)) f))) a_6989586621680287025 |
sGroupAllWith :: forall a b (t1 :: a ~> b) (t2 :: [a]). SOrd b => Sing t1 -> Sing t2 -> Sing (GroupAllWith t1 t2) Source #
type family GroupBy1 (a1 :: a ~> (a ~> Bool)) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
GroupBy1 (eq :: a6989586621680285675 ~> (a6989586621680285675 ~> Bool)) (x ':| xs :: NonEmpty a6989586621680285675) = Apply (Apply ((:|@#@$) :: TyFun (NonEmpty a6989586621680285675) ([NonEmpty a6989586621680285675] ~> NonEmpty (NonEmpty a6989586621680285675)) -> Type) (Apply (Apply ((:|@#@$) :: TyFun a6989586621680285675 ([a6989586621680285675] ~> NonEmpty a6989586621680285675) -> Type) x) (Let6989586621680286997YsSym0 eq x xs))) (Apply (Apply (GroupBySym0 :: TyFun (a6989586621680285675 ~> (a6989586621680285675 ~> Bool)) ([a6989586621680285675] ~> [NonEmpty a6989586621680285675]) -> Type) eq) (Let6989586621680286997ZsSym0 eq x xs)) |
sGroupBy1 :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (GroupBy1 t1 t2) Source #
type family GroupWith1 (a1 :: a ~> b) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
GroupWith1 (f :: a ~> b) (a_6989586621680286980 :: NonEmpty a) = Apply (Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (Apply (Apply (OnSym0 :: TyFun (b ~> (b ~> Bool)) ((a ~> b) ~> (a ~> (a ~> Bool))) -> Type) ((==@#@$) :: TyFun b (b ~> Bool) -> Type)) f)) a_6989586621680286980 |
sGroupWith1 :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). SEq b => Sing t1 -> Sing t2 -> Sing (GroupWith1 t1 t2) Source #
type family GroupAllWith1 (a1 :: a ~> b) (a2 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
GroupAllWith1 (f :: a ~> o) (a_6989586621680286971 :: NonEmpty a) = Apply (Apply (Apply ((.@#@$) :: TyFun (NonEmpty a ~> NonEmpty (NonEmpty a)) ((NonEmpty a ~> NonEmpty a) ~> (NonEmpty a ~> NonEmpty (NonEmpty a))) -> Type) (Apply (GroupWith1Sym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) f)) (Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) f)) a_6989586621680286971 |
sGroupAllWith1 :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). SOrd b => Sing t1 -> Sing t2 -> Sing (GroupAllWith1 t1 t2) Source #
type family IsPrefixOf (a1 :: [a]) (a2 :: NonEmpty a) :: Bool where ... Source #
sIsPrefixOf :: forall a (t1 :: [a]) (t2 :: NonEmpty a). SEq a => Sing t1 -> Sing t2 -> Sing (IsPrefixOf t1 t2) Source #
type family NubBy (a1 :: a ~> (a ~> Bool)) (a2 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
NubBy (eq :: a1 ~> (a1 ~> Bool)) (a2 ':| as :: NonEmpty a1) = Apply (Apply ((:|@#@$) :: TyFun a1 ([a1] ~> NonEmpty a1) -> Type) a2) (Apply (Apply (ListnubBySym0 :: TyFun (a1 ~> (a1 ~> Bool)) ([a1] ~> [a1]) -> Type) eq) (Apply (Apply (ListfilterSym0 :: TyFun (a1 ~> Bool) ([a1] ~> [a1]) -> Type) (LamCases_6989586621680286874Sym0 eq a2 as)) as)) |
sNubBy :: forall a (t1 :: a ~> (a ~> Bool)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (NubBy t1 t2) Source #
(%!!) :: forall a (t1 :: NonEmpty a) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 !! t2) Source #
sZip :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Zip t1 t2) Source #
type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: NonEmpty a) (a3 :: NonEmpty b) :: NonEmpty c where ... Source #
sZipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ZipWith t1 t2 t3) Source #
type family Unzip (a1 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #
Equations
Unzip ('(a2, b2) ':| asbs :: NonEmpty (a1, b1)) = Apply (Apply (Tuple2Sym0 :: TyFun (NonEmpty a1) (NonEmpty b1 ~> (NonEmpty a1, NonEmpty b1)) -> Type) (Apply (Apply ((:|@#@$) :: TyFun a1 ([a1] ~> NonEmpty a1) -> Type) a2) (Let6989586621680286892AsSym0 a2 b2 asbs))) (Apply (Apply ((:|@#@$) :: TyFun b1 ([b1] ~> NonEmpty b1) -> Type) b2) (Let6989586621680286892BsSym0 a2 b2 asbs)) |
Defunctionalization symbols
data (:|@#@$) (a1 :: TyFun a ([a] ~> NonEmpty a)) infixr 5 Source #
Instances
SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679050362 :: a) Source # | |
data (a6989586621679050362 :: a) :|@#@$$ (b :: TyFun [a] (NonEmpty a)) infixr 5 Source #
Instances
SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) Source # | |
SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
SuppressUnusedWarnings ((:|@#@$$) a6989586621679050362 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
type Apply ((:|@#@$$) a6989586621679050362 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679050363 :: [a]) Source # | |
type family (a6989586621679050362 :: a) :|@#@$$$ (a6989586621679050363 :: [a]) :: NonEmpty a where ... infixr 5 Source #
data MapSym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b)) Source #
Instances
SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # | |
SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621680287251 :: a ~> b) Source # | |
data MapSym1 (a6989586621680287251 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty b)) Source #
Instances
SingI1 (MapSym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (MapSym1 a6989586621680287251 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (MapSym1 a6989586621680287251 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621680287252 :: NonEmpty a) Source # | |
type family MapSym2 (a6989586621680287251 :: a ~> b) (a6989586621680287252 :: NonEmpty a) :: NonEmpty b where ... Source #
data IntersperseSym0 (a1 :: TyFun a (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) = IntersperseSym1 a6989586621680287177 |
data IntersperseSym1 (a6989586621680287177 :: a) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI1 (IntersperseSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) # | |
SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (IntersperseSym1 d) # | |
SuppressUnusedWarnings (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287178 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287178 :: NonEmpty a) = Intersperse a6989586621680287177 a6989586621680287178 |
type family IntersperseSym2 (a6989586621680287177 :: a) (a6989586621680287178 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
IntersperseSym2 (a6989586621680287177 :: a) (a6989586621680287178 :: NonEmpty a) = Intersperse a6989586621680287177 a6989586621680287178 |
data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b))) Source #
Instances
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287221 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621680287221 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> NonEmpty b)) Source #
Instances
SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287222 :: b) Source # | |
data ScanlSym2 (a6989586621680287221 :: b ~> (a ~> b)) (a6989586621680287222 :: b) (c :: TyFun [a] (NonEmpty b)) Source #
Instances
SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ScanlSym2 a6989586621680287221 a6989586621680287222 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanlSym2 a6989586621680287221 a6989586621680287222 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287223 :: [a]) Source # | |
type family ScanlSym3 (a6989586621680287221 :: b ~> (a ~> b)) (a6989586621680287222 :: b) (a6989586621680287223 :: [a]) :: NonEmpty b where ... Source #
data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b))) Source #
Instances
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287209 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621680287209 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> NonEmpty b)) Source #
Instances
SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287210 :: b) Source # | |
data ScanrSym2 (a6989586621680287209 :: a ~> (b ~> b)) (a6989586621680287210 :: b) (c :: TyFun [a] (NonEmpty b)) Source #
Instances
SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ScanrSym2 a6989586621680287209 a6989586621680287210 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ScanrSym2 a6989586621680287209 a6989586621680287210 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287211 :: [a]) Source # | |
type family ScanrSym3 (a6989586621680287209 :: a ~> (b ~> b)) (a6989586621680287210 :: b) (a6989586621680287211 :: [a]) :: NonEmpty b where ... Source #
data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287198 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data Scanl1Sym1 (a6989586621680287198 :: a ~> (a ~> a)) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI d => SingI (Scanl1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (Scanl1Sym1 d) # | |
SuppressUnusedWarnings (Scanl1Sym1 a6989586621680287198 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (Scanl1Sym1 a6989586621680287198 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287199 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family Scanl1Sym2 (a6989586621680287198 :: a ~> (a ~> a)) (a6989586621680287199 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
Scanl1Sym2 (a6989586621680287198 :: a ~> (a ~> a)) (a6989586621680287199 :: NonEmpty a) = Scanl1 a6989586621680287198 a6989586621680287199 |
data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287190 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data Scanr1Sym1 (a6989586621680287190 :: a ~> (a ~> a)) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI d => SingI (Scanr1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (Scanr1Sym1 d) # | |
SuppressUnusedWarnings (Scanr1Sym1 a6989586621680287190 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (Scanr1Sym1 a6989586621680287190 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287191 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family Scanr1Sym2 (a6989586621680287190 :: a ~> (a ~> a)) (a6989586621680287191 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
Scanr1Sym2 (a6989586621680287190 :: a ~> (a ~> a)) (a6989586621680287191 :: NonEmpty a) = Scanr1 a6989586621680287190 a6989586621680287191 |
data TransposeSym0 (a1 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a))) Source #
Instances
SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # | |
SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286864 :: NonEmpty (NonEmpty a)) Source # | |
type family TransposeSym1 (a6989586621680286864 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
TransposeSym1 (a6989586621680286864 :: NonEmpty (NonEmpty a)) = Transpose a6989586621680286864 |
data SortBySym0 (a1 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286856 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data SortBySym1 (a6989586621680286856 :: a ~> (a ~> Ordering)) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI d => SingI (SortBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (SortBySym1 d) # | |
SuppressUnusedWarnings (SortBySym1 a6989586621680286856 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (SortBySym1 a6989586621680286856 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286857 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family SortBySym2 (a6989586621680286856 :: a ~> (a ~> Ordering)) (a6989586621680286857 :: NonEmpty a) :: NonEmpty a where ... Source #
data SortWithSym0 (a1 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a)) Source #
Instances
SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) = SortWithSym1 a6989586621680286847 |
data SortWithSym1 (a6989586621680286847 :: a ~> o) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SOrd o => SingI1 (SortWithSym1 :: (a ~> o) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SOrd o, SingI d) => SingI (SortWithSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (SortWithSym1 d) # | |
SuppressUnusedWarnings (SortWithSym1 a6989586621680286847 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SortWithSym1 a6989586621680286847 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286848 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family SortWithSym2 (a6989586621680286847 :: a ~> o) (a6989586621680286848 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
SortWithSym2 (a6989586621680286847 :: a ~> o) (a6989586621680286848 :: NonEmpty a) = SortWith a6989586621680286847 a6989586621680286848 |
data LengthSym0 (a1 :: TyFun (NonEmpty a) Natural) Source #
Instances
SingI (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621680287381 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family LengthSym1 (a6989586621680287381 :: NonEmpty a) :: Natural where ... Source #
Equations
LengthSym1 (a6989586621680287381 :: NonEmpty a) = Length a6989586621680287381 |
data HeadSym0 (a1 :: TyFun (NonEmpty a) a) Source #
Instances
SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287316 :: NonEmpty a) Source # | |
data TailSym0 (a1 :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287312 :: NonEmpty a) Source # | |
data LastSym0 (a1 :: TyFun (NonEmpty a) a) Source #
Instances
SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287307 :: NonEmpty a) Source # | |
data InitSym0 (a1 :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287302 :: NonEmpty a) Source # | |
data (<|@#@$) (a1 :: TyFun a (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287295 :: a) Source # | |
data (a6989586621680287295 :: a) <|@#@$$ (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI1 ((<|@#@$$) :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings ((<|@#@$$) a6989586621680287295 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply ((<|@#@$$) a6989586621680287295 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287296 :: NonEmpty a) Source # | |
type family (a6989586621680287295 :: a) <|@#@$$$ (a6989586621680287296 :: NonEmpty a) :: NonEmpty a where ... Source #
data ConsSym0 (a1 :: TyFun a (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287288 :: a) Source # | |
data ConsSym1 (a6989586621680287288 :: a) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ConsSym1 a6989586621680287288 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ConsSym1 a6989586621680287288 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287289 :: NonEmpty a) Source # | |
type family ConsSym2 (a6989586621680287288 :: a) (a6989586621680287289 :: NonEmpty a) :: NonEmpty a where ... Source #
data UnconsSym0 (a1 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a))) Source #
Instances
SingI (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621680287345 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family UnconsSym1 (a6989586621680287345 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #
Equations
UnconsSym1 (a6989586621680287345 :: NonEmpty a) = Uncons a6989586621680287345 |
data UnfoldrSym0 (a1 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b)) Source #
Instances
SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287321 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data UnfoldrSym1 (a6989586621680287321 :: a ~> (b, Maybe a)) (b1 :: TyFun a (NonEmpty b)) Source #
Instances
SingI1 (UnfoldrSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldrSym1 d) # | |
SuppressUnusedWarnings (UnfoldrSym1 a6989586621680287321 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnfoldrSym1 a6989586621680287321 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287322 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family UnfoldrSym2 (a6989586621680287321 :: a ~> (b, Maybe a)) (a6989586621680287322 :: a) :: NonEmpty b where ... Source #
Equations
UnfoldrSym2 (a6989586621680287321 :: a ~> (b, Maybe a)) (a6989586621680287322 :: a) = Unfoldr a6989586621680287321 a6989586621680287322 |
data SortSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287279 :: NonEmpty a) Source # | |
data ReverseSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287172 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family ReverseSym1 (a6989586621680287172 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
ReverseSym1 (a6989586621680287172 :: NonEmpty a) = Reverse a6989586621680287172 |
data InitsSym0 (a1 :: TyFun [a] (NonEmpty [a])) Source #
Instances
SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
SuppressUnusedWarnings (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287246 :: [a]) Source # | |
data TailsSym0 (a1 :: TyFun [a] (NonEmpty [a])) Source #
Instances
SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
SuppressUnusedWarnings (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287240 :: [a]) Source # | |
data UnfoldSym0 (a1 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b)) Source #
Instances
SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
SuppressUnusedWarnings (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287356 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data UnfoldSym1 (a6989586621680287356 :: a ~> (b, Maybe a)) (b1 :: TyFun a (NonEmpty b)) Source #
Instances
SingI1 (UnfoldSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldSym1 d) # | |
SuppressUnusedWarnings (UnfoldSym1 a6989586621680287356 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnfoldSym1 a6989586621680287356 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287357 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data InsertSym0 (a1 :: TyFun a ([a] ~> NonEmpty a)) Source #
Instances
SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) = InsertSym1 a6989586621680287232 |
data InsertSym1 (a6989586621680287232 :: a) (b :: TyFun [a] (NonEmpty a)) Source #
Instances
SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) # | |
(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (InsertSym1 d) # | |
SuppressUnusedWarnings (InsertSym1 a6989586621680287232 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (InsertSym1 a6989586621680287232 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287233 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family InsertSym2 (a6989586621680287232 :: a) (a6989586621680287233 :: [a]) :: NonEmpty a where ... Source #
Equations
InsertSym2 (a6989586621680287232 :: a) (a6989586621680287233 :: [a]) = Insert a6989586621680287232 a6989586621680287233 |
data TakeSym0 (a1 :: TyFun Natural (NonEmpty a ~> [a])) Source #
Instances
SingI (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287164 :: Natural) Source # | |
data TakeSym1 (a6989586621680287164 :: Natural) (b :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
SuppressUnusedWarnings (TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287165 :: NonEmpty a) Source # | |
type family TakeSym2 (a6989586621680287164 :: Natural) (a6989586621680287165 :: NonEmpty a) :: [a] where ... Source #
data DropSym0 (a1 :: TyFun Natural (NonEmpty a ~> [a])) Source #
Instances
SingI (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287155 :: Natural) Source # | |
data DropSym1 (a6989586621680287155 :: Natural) (b :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
SuppressUnusedWarnings (DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287156 :: NonEmpty a) Source # | |
type family DropSym2 (a6989586621680287155 :: Natural) (a6989586621680287156 :: NonEmpty a) :: [a] where ... Source #
data SplitAtSym0 (a1 :: TyFun Natural (NonEmpty a ~> ([a], [a]))) Source #
Instances
SingI (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287146 :: Natural) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data SplitAtSym1 (a6989586621680287146 :: Natural) (b :: TyFun (NonEmpty a) ([a], [a])) Source #
Instances
SingI1 (SplitAtSym1 :: Natural -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SingI d => SingI (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287147 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family SplitAtSym2 (a6989586621680287146 :: Natural) (a6989586621680287147 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
SplitAtSym2 a6989586621680287146 (a6989586621680287147 :: NonEmpty a) = SplitAt a6989586621680287146 a6989586621680287147 |
data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a])) Source #
Instances
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287137 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data TakeWhileSym1 (a6989586621680287137 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI d => SingI (TakeWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (TakeWhileSym1 d) # | |
SuppressUnusedWarnings (TakeWhileSym1 a6989586621680287137 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (TakeWhileSym1 a6989586621680287137 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287138 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family TakeWhileSym2 (a6989586621680287137 :: a ~> Bool) (a6989586621680287138 :: NonEmpty a) :: [a] where ... Source #
Equations
TakeWhileSym2 (a6989586621680287137 :: a ~> Bool) (a6989586621680287138 :: NonEmpty a) = TakeWhile a6989586621680287137 a6989586621680287138 |
data DropWhileSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a])) Source #
Instances
SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287128 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data DropWhileSym1 (a6989586621680287128 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI d => SingI (DropWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (DropWhileSym1 d) # | |
SuppressUnusedWarnings (DropWhileSym1 a6989586621680287128 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (DropWhileSym1 a6989586621680287128 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287129 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family DropWhileSym2 (a6989586621680287128 :: a ~> Bool) (a6989586621680287129 :: NonEmpty a) :: [a] where ... Source #
Equations
DropWhileSym2 (a6989586621680287128 :: a ~> Bool) (a6989586621680287129 :: NonEmpty a) = DropWhile a6989586621680287128 a6989586621680287129 |
data SpanSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a]))) Source #
Instances
SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287119 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621680287119 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a])) Source #
Instances
SingI d => SingI (SpanSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (SpanSym1 a6989586621680287119 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
type Apply (SpanSym1 a6989586621680287119 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287120 :: NonEmpty a) Source # | |
type family SpanSym2 (a6989586621680287119 :: a ~> Bool) (a6989586621680287120 :: NonEmpty a) :: ([a], [a]) where ... Source #
data BreakSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a]))) Source #
Instances
SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287110 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621680287110 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a])) Source #
Instances
SingI d => SingI (BreakSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (BreakSym1 a6989586621680287110 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
type Apply (BreakSym1 a6989586621680287110 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287111 :: NonEmpty a) Source # | |
type family BreakSym2 (a6989586621680287110 :: a ~> Bool) (a6989586621680287111 :: NonEmpty a) :: ([a], [a]) where ... Source #
data FilterSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> [a])) Source #
Instances
SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287101 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data FilterSym1 (a6989586621680287101 :: a ~> Bool) (b :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI d => SingI (FilterSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (FilterSym1 d) # | |
SuppressUnusedWarnings (FilterSym1 a6989586621680287101 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (FilterSym1 a6989586621680287101 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287102 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family FilterSym2 (a6989586621680287101 :: a ~> Bool) (a6989586621680287102 :: NonEmpty a) :: [a] where ... Source #
Equations
FilterSym2 (a6989586621680287101 :: a ~> Bool) (a6989586621680287102 :: NonEmpty a) = Filter a6989586621680287101 a6989586621680287102 |
data PartitionSym0 (a1 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a]))) Source #
Instances
SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287092 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data PartitionSym1 (a6989586621680287092 :: a ~> Bool) (b :: TyFun (NonEmpty a) ([a], [a])) Source #
Instances
SingI d => SingI (PartitionSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (PartitionSym1 d) # | |
SuppressUnusedWarnings (PartitionSym1 a6989586621680287092 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (PartitionSym1 a6989586621680287092 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287093 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family PartitionSym2 (a6989586621680287092 :: a ~> Bool) (a6989586621680287093 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
PartitionSym2 (a6989586621680287092 :: a ~> Bool) (a6989586621680287093 :: NonEmpty a) = Partition a6989586621680287092 a6989586621680287093 |
data GroupSym0 (a1 :: TyFun [a] [NonEmpty a]) Source #
Instances
SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287085 :: [a]) Source # | |
data GroupBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a])) Source #
Instances
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287048 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data GroupBySym1 (a6989586621680287048 :: a ~> (a ~> Bool)) (b :: TyFun [a] [NonEmpty a]) Source #
Instances
SingI d => SingI (GroupBySym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupBySym1 d) # | |
SuppressUnusedWarnings (GroupBySym1 a6989586621680287048 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (GroupBySym1 a6989586621680287048 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287049 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family GroupBySym2 (a6989586621680287048 :: a ~> (a ~> Bool)) (a6989586621680287049 :: [a]) :: [NonEmpty a] where ... Source #
Equations
GroupBySym2 (a6989586621680287048 :: a ~> (a ~> Bool)) (a6989586621680287049 :: [a]) = GroupBy a6989586621680287048 a6989586621680287049 |
data GroupWithSym0 (a1 :: TyFun (a ~> b) ([a] ~> [NonEmpty a])) Source #
Instances
SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) = GroupWithSym1 a6989586621680287039 |
data GroupWithSym1 (a6989586621680287039 :: a ~> b) (b1 :: TyFun [a] [NonEmpty a]) Source #
Instances
SEq b => SingI1 (GroupWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SEq b, SingI d) => SingI (GroupWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupWithSym1 d) # | |
SuppressUnusedWarnings (GroupWithSym1 a6989586621680287039 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupWithSym1 a6989586621680287039 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287040 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family GroupWithSym2 (a6989586621680287039 :: a ~> b) (a6989586621680287040 :: [a]) :: [NonEmpty a] where ... Source #
Equations
GroupWithSym2 (a6989586621680287039 :: a ~> b) (a6989586621680287040 :: [a]) = GroupWith a6989586621680287039 a6989586621680287040 |
data GroupAllWithSym0 (a1 :: TyFun (a ~> b) ([a] ~> [NonEmpty a])) Source #
Instances
SOrd b => SingI (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) = GroupAllWithSym1 a6989586621680287030 |
data GroupAllWithSym1 (a6989586621680287030 :: a ~> b) (b1 :: TyFun [a] [NonEmpty a]) Source #
Instances
SOrd b => SingI1 (GroupAllWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SOrd b, SingI d) => SingI (GroupAllWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupAllWithSym1 d) # | |
SuppressUnusedWarnings (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287031 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287031 :: [a]) = GroupAllWith a6989586621680287030 a6989586621680287031 |
type family GroupAllWithSym2 (a6989586621680287030 :: a ~> b) (a6989586621680287031 :: [a]) :: [NonEmpty a] where ... Source #
Equations
GroupAllWithSym2 (a6989586621680287030 :: a ~> b) (a6989586621680287031 :: [a]) = GroupAllWith a6989586621680287030 a6989586621680287031 |
data Group1Sym0 (a1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
SEq a => SingI (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680287023 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family Group1Sym1 (a6989586621680287023 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
Group1Sym1 (a6989586621680287023 :: NonEmpty a) = Group1 a6989586621680287023 |
data GroupBy1Sym0 (a1 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a))) Source #
Instances
SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286992 :: a ~> (a ~> Bool)) Source # | |
data GroupBy1Sym1 (a6989586621680286992 :: a ~> (a ~> Bool)) (b :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
SingI d => SingI (GroupBy1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupBy1Sym1 d) # | |
SuppressUnusedWarnings (GroupBy1Sym1 a6989586621680286992 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (GroupBy1Sym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type Apply (GroupBy1Sym1 a6989586621680286992 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286993 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family GroupBy1Sym2 (a6989586621680286992 :: a ~> (a ~> Bool)) (a6989586621680286993 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
data GroupWith1Sym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a))) Source #
Instances
SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286985 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data GroupWith1Sym1 (a6989586621680286985 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
SEq b => SingI1 (GroupWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SEq b, SingI d) => SingI (GroupWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupWith1Sym1 d) # | |
SuppressUnusedWarnings (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286986 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286986 :: NonEmpty a) = GroupWith1 a6989586621680286985 a6989586621680286986 |
type family GroupWith1Sym2 (a6989586621680286985 :: a ~> b) (a6989586621680286986 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
GroupWith1Sym2 (a6989586621680286985 :: a ~> b) (a6989586621680286986 :: NonEmpty a) = GroupWith1 a6989586621680286985 a6989586621680286986 |
data GroupAllWith1Sym0 (a1 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a))) Source #
Instances
SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286976 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data GroupAllWith1Sym1 (a6989586621680286976 :: a ~> b) (b1 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
SOrd b => SingI1 (GroupAllWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SOrd b, SingI d) => SingI (GroupAllWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (GroupAllWith1Sym1 d) # | |
SuppressUnusedWarnings (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286977 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286977 :: NonEmpty a) = GroupAllWith1 a6989586621680286976 a6989586621680286977 |
type family GroupAllWith1Sym2 (a6989586621680286976 :: a ~> b) (a6989586621680286977 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
GroupAllWith1Sym2 (a6989586621680286976 :: a ~> b) (a6989586621680286977 :: NonEmpty a) = GroupAllWith1 a6989586621680286976 a6989586621680286977 |
data IsPrefixOfSym0 (a1 :: TyFun [a] (NonEmpty a ~> Bool)) Source #
Instances
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) = IsPrefixOfSym1 a6989586621680286965 |
data IsPrefixOfSym1 (a6989586621680286965 :: [a]) (b :: TyFun (NonEmpty a) Bool) Source #
Instances
SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) # | |
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (IsPrefixOfSym1 d) # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680286966 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680286966 :: NonEmpty a) = IsPrefixOf a6989586621680286965 a6989586621680286966 |
type family IsPrefixOfSym2 (a6989586621680286965 :: [a]) (a6989586621680286966 :: NonEmpty a) :: Bool where ... Source #
Equations
IsPrefixOfSym2 (a6989586621680286965 :: [a]) (a6989586621680286966 :: NonEmpty a) = IsPrefixOf a6989586621680286965 a6989586621680286966 |
data NubSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286884 :: NonEmpty a) Source # | |
data NubBySym0 (a1 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a)) Source #
Instances
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286869 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621680286869 :: a ~> (a ~> Bool)) (b :: TyFun (NonEmpty a) (NonEmpty a)) Source #
Instances
SingI d => SingI (NubBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (NubBySym1 a6989586621680286869 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
type Apply (NubBySym1 a6989586621680286869 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286870 :: NonEmpty a) Source # | |
type family NubBySym2 (a6989586621680286869 :: a ~> (a ~> Bool)) (a6989586621680286870 :: NonEmpty a) :: NonEmpty a where ... Source #
data (!!@#@$) (a1 :: TyFun (NonEmpty a) (Natural ~> a)) Source #
Instances
SingI ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # | |
SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621680286938 :: NonEmpty a) Source # | |
data (a6989586621680286938 :: NonEmpty a) !!@#@$$ (b :: TyFun Natural a) Source #
Instances
SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # | |
SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings ((!!@#@$$) a6989586621680286938 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply ((!!@#@$$) a6989586621680286938 :: TyFun Natural a -> Type) (a6989586621680286939 :: Natural) Source # | |
type family (a6989586621680286938 :: NonEmpty a) !!@#@$$$ (a6989586621680286939 :: Natural) :: a where ... Source #
data ZipSym0 (a1 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b))) Source #
Instances
SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621680286929 :: NonEmpty a) Source # | |
data ZipSym1 (a6989586621680286929 :: NonEmpty a) (b1 :: TyFun (NonEmpty b) (NonEmpty (a, b))) Source #
Instances
SingI1 (ZipSym1 :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
SuppressUnusedWarnings (ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621680286930 :: NonEmpty b) Source # | |
type family ZipSym2 (a6989586621680286929 :: NonEmpty a) (a6989586621680286930 :: NonEmpty b) :: NonEmpty (a, b) where ... Source #
data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c))) Source #
Instances
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # | |
SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680286918 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.NonEmpty.Singletons |
data ZipWithSym1 (a6989586621680286918 :: a ~> (b ~> c)) (b1 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c)) Source #
Instances
SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SingI d => SingI (ZipWithSym1 d :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (ZipWithSym1 d) # | |
SuppressUnusedWarnings (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) = ZipWithSym2 a6989586621680286918 a6989586621680286919 |
data ZipWithSym2 (a6989586621680286918 :: a ~> (b ~> c)) (a6989586621680286919 :: NonEmpty a) (c1 :: TyFun (NonEmpty b) (NonEmpty c)) Source #
Instances
SingI d => SingI1 (ZipWithSym2 d :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (ZipWithSym2 d1 d2) # | |
SuppressUnusedWarnings (ZipWithSym2 a6989586621680286918 a6989586621680286919 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ZipWithSym2 a6989586621680286918 a6989586621680286919 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680286920 :: NonEmpty b) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family ZipWithSym3 (a6989586621680286918 :: a ~> (b ~> c)) (a6989586621680286919 :: NonEmpty a) (a6989586621680286920 :: NonEmpty b) :: NonEmpty c where ... Source #
data UnzipSym0 (a1 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b)) Source #
Instances
SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # | |
SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621680286888 :: NonEmpty (a, b)) Source # | |
type family UnzipSym1 (a6989586621680286888 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #
data FromListSym0 (a1 :: TyFun [a] (NonEmpty a)) Source #
Instances
SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287272 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family FromListSym1 (a6989586621680287272 :: [a]) :: NonEmpty a where ... Source #
Equations
FromListSym1 (a6989586621680287272 :: [a]) = FromList a6989586621680287272 |
data ToListSym0 (a1 :: TyFun (NonEmpty a) [a]) Source #
Instances
SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287267 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family ToListSym1 (a6989586621680287267 :: NonEmpty a) :: [a] where ... Source #
Equations
ToListSym1 (a6989586621680287267 :: NonEmpty a) = ToList a6989586621680287267 |
data NonEmpty_Sym0 (a1 :: TyFun [a] (Maybe (NonEmpty a))) Source #
Instances
SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621680287350 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons |
type family NonEmpty_Sym1 (a6989586621680287350 :: [a]) :: Maybe (NonEmpty a) where ... Source #
Equations
NonEmpty_Sym1 (a6989586621680287350 :: [a]) = NonEmpty_ a6989586621680287350 |
data XorSym0 (a :: TyFun (NonEmpty Bool) Bool) Source #
Instances
SingI XorSym0 Source # | |
Defined in Data.List.NonEmpty.Singletons | |
SuppressUnusedWarnings XorSym0 Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
type Apply XorSym0 (a6989586621680287370 :: NonEmpty Bool) Source # | |
Orphan instances
PMonadZip NonEmpty Source # | |
SMonadZip NonEmpty Source # | |
Methods sMzip :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Mzip t1 t2) Source # sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (MzipWith t1 t2 t3) Source # sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Munzip t) Source # |