| Copyright | (C) 2016 Richard Eisenberg |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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 :: forall (a :: Type). NonEmpty a -> Type where
- type family Map (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty b where ...
- sMap :: forall a b (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b)
- type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
- sIntersperse :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a)
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
- sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: NonEmpty b)
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
- sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b)
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
- sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a)
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
- sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a)
- type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- sTranspose :: forall a (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a))
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ...
- sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a)
- type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ...
- sSortWith :: forall a o (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a)
- type family Length (a :: NonEmpty a) :: Nat where ...
- sLength :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Nat)
- type family Head (a :: NonEmpty a) :: a where ...
- sHead :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply HeadSym0 t :: a)
- type family Tail (a :: NonEmpty a) :: [a] where ...
- sTail :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply TailSym0 t :: [a])
- type family Last (a :: NonEmpty a) :: a where ...
- sLast :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LastSym0 t :: a)
- type family Init (a :: NonEmpty a) :: [a] where ...
- sInit :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply InitSym0 t :: [a])
- type family (a :: a) <| (a :: NonEmpty a) :: NonEmpty a where ...
- (%<|) :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a)
- type family Cons (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
- sCons :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a)
- type family Uncons (a :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a)))
- type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
- sUnfoldr :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b)
- type family Sort (a :: NonEmpty a) :: NonEmpty a where ...
- sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a)
- type family Reverse (a :: NonEmpty a) :: NonEmpty a where ...
- sReverse :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a)
- type family Inits (a :: [a]) :: NonEmpty [a] where ...
- sInits :: forall a (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: NonEmpty [a])
- type family Tails (a :: [a]) :: NonEmpty [a] where ...
- sTails :: forall a (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: NonEmpty [a])
- type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
- sUnfold :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b)
- type family Insert (a :: a) (a :: [a]) :: NonEmpty a where ...
- sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a)
- type family Take (a :: Nat) (a :: NonEmpty a) :: [a] where ...
- sTake :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Nat) (a :: NonEmpty a) :: [a] where ...
- sDrop :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Nat) (a :: NonEmpty a) :: ([a], [a]) where ...
- sSplitAt :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a]))
- type family TakeWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sTakeWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a])
- type family DropWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sDropWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a])
- type family Span (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sSpan :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a]))
- type family Break (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sBreak :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a]))
- type family Filter (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sFilter :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a])
- type family Partition (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sPartition :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a]))
- type family Group (a :: [a]) :: [NonEmpty a] where ...
- sGroup :: forall a (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [NonEmpty a])
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [NonEmpty a] where ...
- sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a])
- type family GroupWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
- sGroupWith :: forall a b (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a])
- type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
- sGroupAllWith :: forall a b (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a])
- type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroup1 :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a))
- type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupBy1 :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a))
- type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a))
- type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupAllWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a))
- type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ...
- sIsPrefixOf :: forall a (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool)
- type family Nub (a :: NonEmpty a) :: NonEmpty a where ...
- sNub :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a)
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty a where ...
- sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a)
- type family (a :: NonEmpty a) !! (a :: Nat) :: a where ...
- (%!!) :: forall a (t :: NonEmpty a) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a)
- type family Zip (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty (a, b) where ...
- sZip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b))
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ...
- sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: NonEmpty c)
- type family Unzip (a :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b))
- type family FromList (a :: [a]) :: NonEmpty a where ...
- sFromList :: forall a (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a)
- type family ToList (a :: NonEmpty a) :: [a] where ...
- sToList :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply ToListSym0 t :: [a])
- type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ...
- sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a))
- type family Xor (a :: NonEmpty Bool) :: Bool where ...
- sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool)
- data (:|@#@$) :: (~>) a ((~>) [a] (NonEmpty (a :: Type)))
- data (:|@#@$$) (a6989586621679041897 :: a) :: (~>) [a] (NonEmpty (a :: Type))
- type family (a6989586621679041897 :: a) :|@#@$$$ (a6989586621679041898 :: [a]) :: NonEmpty (a :: Type) where ...
- data MapSym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty b))
- data MapSym1 (a6989586621681120713 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b)
- type family MapSym2 (a6989586621681120713 :: (~>) a b) (a6989586621681120714 :: NonEmpty a) :: NonEmpty b where ...
- data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data IntersperseSym1 (a6989586621681120641 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family IntersperseSym2 (a6989586621681120641 :: a) (a6989586621681120642 :: NonEmpty a) :: NonEmpty a where ...
- data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanlSym1 (a6989586621681120683 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanlSym2 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanlSym3 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) (a6989586621681120685 :: [a]) :: NonEmpty b where ...
- data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanrSym1 (a6989586621681120671 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanrSym2 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanrSym3 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) (a6989586621681120673 :: [a]) :: NonEmpty b where ...
- data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanl1Sym1 (a6989586621681120660 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanl1Sym2 (a6989586621681120660 :: (~>) a ((~>) a a)) (a6989586621681120661 :: NonEmpty a) :: NonEmpty a where ...
- data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanr1Sym1 (a6989586621681120652 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanr1Sym2 (a6989586621681120652 :: (~>) a ((~>) a a)) (a6989586621681120653 :: NonEmpty a) :: NonEmpty a where ...
- data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a))
- type family TransposeSym1 (a6989586621681120350 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (NonEmpty a) (NonEmpty a))
- data SortBySym1 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortBySym2 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) (a6989586621681120343 :: NonEmpty a) :: NonEmpty a where ...
- data SortWithSym0 :: (~>) ((~>) a o) ((~>) (NonEmpty a) (NonEmpty a))
- data SortWithSym1 (a6989586621681120333 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortWithSym2 (a6989586621681120333 :: (~>) a o) (a6989586621681120334 :: NonEmpty a) :: NonEmpty a where ...
- data LengthSym0 :: (~>) (NonEmpty a) Nat
- type family LengthSym1 (a6989586621681120843 :: NonEmpty a) :: Nat where ...
- data HeadSym0 :: (~>) (NonEmpty a) a
- type family HeadSym1 (a6989586621681120778 :: NonEmpty a) :: a where ...
- data TailSym0 :: (~>) (NonEmpty a) [a]
- type family TailSym1 (a6989586621681120774 :: NonEmpty a) :: [a] where ...
- data LastSym0 :: (~>) (NonEmpty a) a
- type family LastSym1 (a6989586621681120769 :: NonEmpty a) :: a where ...
- data InitSym0 :: (~>) (NonEmpty a) [a]
- type family InitSym1 (a6989586621681120764 :: NonEmpty a) :: [a] where ...
- data (<|@#@$) :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data (<|@#@$$) (a6989586621681120757 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family (a6989586621681120757 :: a) <|@#@$$$ (a6989586621681120758 :: NonEmpty a) :: NonEmpty a where ...
- data ConsSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data ConsSym1 (a6989586621681120750 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family ConsSym2 (a6989586621681120750 :: a) (a6989586621681120751 :: NonEmpty a) :: NonEmpty a where ...
- data UnconsSym0 :: (~>) (NonEmpty a) (a, Maybe (NonEmpty a))
- type family UnconsSym1 (a6989586621681120807 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- data UnfoldrSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldrSym1 (a6989586621681120783 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- type family UnfoldrSym2 (a6989586621681120783 :: (~>) a (b, Maybe a)) (a6989586621681120784 :: a) :: NonEmpty b where ...
- data SortSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortSym1 (a6989586621681120741 :: NonEmpty a) :: NonEmpty a where ...
- data ReverseSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family ReverseSym1 (a6989586621681120636 :: NonEmpty a) :: NonEmpty a where ...
- data InitsSym0 :: (~>) [a] (NonEmpty [a])
- type family InitsSym1 (a6989586621681120708 :: [a]) :: NonEmpty [a] where ...
- data TailsSym0 :: (~>) [a] (NonEmpty [a])
- type family TailsSym1 (a6989586621681120702 :: [a]) :: NonEmpty [a] where ...
- data UnfoldSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldSym1 (a6989586621681120818 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- data InsertSym0 :: (~>) a ((~>) [a] (NonEmpty a))
- data InsertSym1 (a6989586621681120694 :: a) :: (~>) [a] (NonEmpty a)
- type family InsertSym2 (a6989586621681120694 :: a) (a6989586621681120695 :: [a]) :: NonEmpty a where ...
- data TakeSym0 :: (~>) Nat ((~>) (NonEmpty a) [a])
- data TakeSym1 (a6989586621681120628 :: Nat) :: (~>) (NonEmpty a) [a]
- type family TakeSym2 (a6989586621681120628 :: Nat) (a6989586621681120629 :: NonEmpty a) :: [a] where ...
- data DropSym0 :: (~>) Nat ((~>) (NonEmpty a) [a])
- data DropSym1 (a6989586621681120619 :: Nat) :: (~>) (NonEmpty a) [a]
- type family DropSym2 (a6989586621681120619 :: Nat) (a6989586621681120620 :: NonEmpty a) :: [a] where ...
- data SplitAtSym0 :: (~>) Nat ((~>) (NonEmpty a) ([a], [a]))
- data SplitAtSym1 (a6989586621681120610 :: Nat) :: (~>) (NonEmpty a) ([a], [a])
- type family SplitAtSym2 (a6989586621681120610 :: Nat) (a6989586621681120611 :: NonEmpty a) :: ([a], [a]) where ...
- data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data TakeWhileSym1 (a6989586621681120601 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family TakeWhileSym2 (a6989586621681120601 :: (~>) a Bool) (a6989586621681120602 :: NonEmpty a) :: [a] where ...
- data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data DropWhileSym1 (a6989586621681120592 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family DropWhileSym2 (a6989586621681120592 :: (~>) a Bool) (a6989586621681120593 :: NonEmpty a) :: [a] where ...
- data SpanSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data SpanSym1 (a6989586621681120583 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family SpanSym2 (a6989586621681120583 :: (~>) a Bool) (a6989586621681120584 :: NonEmpty a) :: ([a], [a]) where ...
- data BreakSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data BreakSym1 (a6989586621681120574 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family BreakSym2 (a6989586621681120574 :: (~>) a Bool) (a6989586621681120575 :: NonEmpty a) :: ([a], [a]) where ...
- data FilterSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data FilterSym1 (a6989586621681120565 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family FilterSym2 (a6989586621681120565 :: (~>) a Bool) (a6989586621681120566 :: NonEmpty a) :: [a] where ...
- data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data PartitionSym1 (a6989586621681120556 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family PartitionSym2 (a6989586621681120556 :: (~>) a Bool) (a6989586621681120557 :: NonEmpty a) :: ([a], [a]) where ...
- data GroupSym0 :: (~>) [a] [NonEmpty a]
- type family GroupSym1 (a6989586621681120549 :: [a]) :: [NonEmpty a] where ...
- data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [NonEmpty a])
- data GroupBySym1 (a6989586621681120516 :: (~>) a ((~>) a Bool)) :: (~>) [a] [NonEmpty a]
- type family GroupBySym2 (a6989586621681120516 :: (~>) a ((~>) a Bool)) (a6989586621681120517 :: [a]) :: [NonEmpty a] where ...
- data GroupWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupWithSym1 (a6989586621681120507 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupWithSym2 (a6989586621681120507 :: (~>) a b) (a6989586621681120508 :: [a]) :: [NonEmpty a] where ...
- data GroupAllWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupAllWithSym1 (a6989586621681120498 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupAllWithSym2 (a6989586621681120498 :: (~>) a b) (a6989586621681120499 :: [a]) :: [NonEmpty a] where ...
- data Group1Sym0 :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family Group1Sym1 (a6989586621681120491 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupBy1Sym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupBy1Sym1 (a6989586621681120464 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupBy1Sym2 (a6989586621681120464 :: (~>) a ((~>) a Bool)) (a6989586621681120465 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupWith1Sym1 (a6989586621681120457 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupWith1Sym2 (a6989586621681120457 :: (~>) a b) (a6989586621681120458 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupAllWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupAllWith1Sym1 (a6989586621681120448 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupAllWith1Sym2 (a6989586621681120448 :: (~>) a b) (a6989586621681120449 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool)
- data IsPrefixOfSym1 (a6989586621681120437 :: [a]) :: (~>) (NonEmpty a) Bool
- type family IsPrefixOfSym2 (a6989586621681120437 :: [a]) (a6989586621681120438 :: NonEmpty a) :: Bool where ...
- data NubSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubSym1 (a6989586621681120368 :: NonEmpty a) :: NonEmpty a where ...
- data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty a))
- data NubBySym1 (a6989586621681120355 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubBySym2 (a6989586621681120355 :: (~>) a ((~>) a Bool)) (a6989586621681120356 :: NonEmpty a) :: NonEmpty a where ...
- data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Nat a)
- data (!!@#@$$) (a6989586621681120418 :: NonEmpty a) :: (~>) Nat a
- type family (a6989586621681120418 :: NonEmpty a) !!@#@$$$ (a6989586621681120419 :: Nat) :: a where ...
- data ZipSym0 :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty (a, b)))
- data ZipSym1 (a6989586621681120409 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b))
- type family ZipSym2 (a6989586621681120409 :: NonEmpty a) (a6989586621681120410 :: NonEmpty b) :: NonEmpty (a, b) where ...
- data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)))
- data ZipWithSym1 (a6989586621681120398 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c))
- data ZipWithSym2 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c)
- type family ZipWithSym3 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) (a6989586621681120400 :: NonEmpty b) :: NonEmpty c where ...
- data UnzipSym0 :: (~>) (NonEmpty (a, b)) (NonEmpty a, NonEmpty b)
- type family UnzipSym1 (a6989586621681120372 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- data FromListSym0 :: (~>) [a] (NonEmpty a)
- type family FromListSym1 (a6989586621681120734 :: [a]) :: NonEmpty a where ...
- data ToListSym0 :: (~>) (NonEmpty a) [a]
- type family ToListSym1 (a6989586621681120729 :: NonEmpty a) :: [a] where ...
- data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a))
- type family NonEmpty_Sym1 (a6989586621681120812 :: [a]) :: Maybe (NonEmpty a) where ...
- data XorSym0 :: (~>) (NonEmpty Bool) Bool
- type family XorSym1 (a6989586621681120832 :: NonEmpty Bool) :: Bool where ...
The NonEmpty singleton
type family Sing :: k -> Type #
The singleton kind-indexed type family.
Instances
data SNonEmpty :: forall (a :: Type). NonEmpty a -> Type where Source #
Constructors
| (:%|) :: forall (a :: Type) (n :: a) (n :: [a]). (Sing n) -> (Sing n) -> SNonEmpty ('(:|) n n :: NonEmpty (a :: Type)) 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 # | |
Non-empty stream transformations
sMap :: forall a b (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) Source #
type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Intersperse a ('(:|) b bs) = Apply (Apply (:|@#@$) b) (Case_6989586621681120646 a b bs bs) |
sIntersperse :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a) Source #
sScanl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanlSym0 t) t) t :: NonEmpty b) Source #
sScanr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: [a]). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ScanrSym0 t) t) t :: NonEmpty b) Source #
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) Source #
sScanr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) Source #
type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Transpose a_6989586621681120346 = Apply (Apply (Apply (.@#@$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply (.@#@$) ListtransposeSym0) (Apply (Apply (.@#@$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621681120346 |
sTranspose :: forall a (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a)) Source #
type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ... Source #
sSortBy :: forall a (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a) Source #
type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortWith a_6989586621681120326 a_6989586621681120328 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681120326) a_6989586621681120328 |
sSortWith :: forall a o (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a) Source #
(%<|) :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a) Source #
sCons :: forall a (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a) Source #
type family Uncons (a :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #
Equations
| Uncons ('(:|) a as) = Apply (Apply Tuple2Sym0 a) (Apply NonEmpty_Sym0 as) |
sUncons :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) Source #
type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #
Equations
| Unfoldr f a = Case_6989586621681120800 f a (Let6989586621681120798Scrutinee_6989586621681119224Sym2 f a) |
sUnfoldr :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) Source #
sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) Source #
type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #
Equations
| Unfold f a = Case_6989586621681120824 f a (Let6989586621681120822Scrutinee_6989586621681119214Sym2 f a) |
sUnfold :: forall a b (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) Source #
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) Source #
sTake :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
sDrop :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
sSplitAt :: forall a (t :: Nat) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
sTakeWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
sDropWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
sSpan :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) Source #
sBreak :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) Source #
sFilter :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
sPartition :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) Source #
type family Group (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| Group a_6989586621681120545 = Apply (Apply GroupBySym0 (==@#@$)) a_6989586621681120545 |
sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a]) Source #
sGroupWith :: forall a b (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a]) Source #
type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupAllWith f a_6989586621681120493 = Apply (Apply (Apply (.@#@$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621681120493 |
sGroupAllWith :: forall a b (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a]) Source #
type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Group1 a_6989586621681120487 = Apply (Apply GroupBy1Sym0 (==@#@$)) a_6989586621681120487 |
sGroup1 :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) Source #
type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
sGroupBy1 :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #
type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupWith1 f a_6989586621681120452 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681120452 |
sGroupWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #
type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupAllWith1 f a_6989586621681120443 = Apply (Apply (Apply (.@#@$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621681120443 |
sGroupAllWith1 :: forall a b (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) Source #
type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ... Source #
sIsPrefixOf :: forall a (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) Source #
sNub :: forall a (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a) Source #
sNubBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a) Source #
type family (a :: NonEmpty a) !! (a :: Nat) :: a where ... Source #
Equations
| arg_6989586621681119236 !! arg_6989586621681119238 = Case_6989586621681120422 arg_6989586621681119236 arg_6989586621681119238 (Apply (Apply Tuple2Sym0 arg_6989586621681119236) arg_6989586621681119238) |
(%!!) :: forall a (t :: NonEmpty a) (t :: Nat). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) Source #
sZip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) Source #
type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ... Source #
sZipWith :: forall a b c (t :: (~>) a ((~>) b c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ZipWithSym0 t) t) t :: NonEmpty c) Source #
sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) Source #
sNonEmpty_ :: forall a (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) Source #
Defunctionalization symbols
data (:|@#@$) :: (~>) a ((~>) [a] (NonEmpty (a :: Type))) infixr 5 Source #
Instances
| SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679041897 :: a) Source # | |
data (:|@#@$$) (a6989586621679041897 :: a) :: (~>) [a] (NonEmpty (a :: Type)) infixr 5 Source #
Instances
| SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:|@#@$$) a6989586621679041897 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:|@#@$$) a6989586621679041897 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679041898 :: [a]) Source # | |
type family (a6989586621679041897 :: a) :|@#@$$$ (a6989586621679041898 :: [a]) :: NonEmpty (a :: Type) where ... infixr 5 Source #
data MapSym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty b)) Source #
Instances
| SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120713 :: a ~> b) Source # | |
data MapSym1 (a6989586621681120713 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b) Source #
Instances
| SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621681120713 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621681120713 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681120714 :: NonEmpty a) Source # | |
type family MapSym2 (a6989586621681120713 :: (~>) a b) (a6989586621681120714 :: NonEmpty a) :: NonEmpty b where ... Source #
data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing IntersperseSym0 # | |
| 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) (a6989586621681120641 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120641 :: a) = IntersperseSym1 a6989586621681120641 | |
data IntersperseSym1 (a6989586621681120641 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| 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 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120642 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym1 a6989586621681120641 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120642 :: NonEmpty a) = Intersperse a6989586621681120641 a6989586621681120642 | |
type family IntersperseSym2 (a6989586621681120641 :: a) (a6989586621681120642 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| IntersperseSym2 a6989586621681120641 a6989586621681120642 = Intersperse a6989586621681120641 a6989586621681120642 |
data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] (NonEmpty b))) Source #
Instances
| SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120683 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621681120683 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621681120683 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621681120683 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120684 :: b) Source # | |
data ScanlSym2 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| (SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym2 a6989586621681120683 a6989586621681120684 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621681120683 a6989586621681120684 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120685 :: [a]) Source # | |
type family ScanlSym3 (a6989586621681120683 :: (~>) b ((~>) a b)) (a6989586621681120684 :: b) (a6989586621681120685 :: [a]) :: NonEmpty b where ... Source #
data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] (NonEmpty b))) Source #
Instances
| SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120671 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621681120671 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621681120671 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621681120671 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120672 :: b) Source # | |
data ScanrSym2 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| (SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym2 a6989586621681120671 a6989586621681120672 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621681120671 a6989586621681120672 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120673 :: [a]) Source # | |
type family ScanrSym3 (a6989586621681120671 :: (~>) a ((~>) b b)) (a6989586621681120672 :: b) (a6989586621681120673 :: [a]) :: NonEmpty b where ... Source #
data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing Scanl1Sym0 # | |
| 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) (a6989586621681120660 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data Scanl1Sym1 (a6989586621681120660 :: (~>) a ((~>) a a)) :: (~>) (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 a6989586621681120660 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanl1Sym1 a6989586621681120660 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120661 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Scanl1Sym2 (a6989586621681120660 :: (~>) a ((~>) a a)) (a6989586621681120661 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanl1Sym2 a6989586621681120660 a6989586621681120661 = Scanl1 a6989586621681120660 a6989586621681120661 |
data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing Scanr1Sym0 # | |
| 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) (a6989586621681120652 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data Scanr1Sym1 (a6989586621681120652 :: (~>) a ((~>) a a)) :: (~>) (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 a6989586621681120652 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (Scanr1Sym1 a6989586621681120652 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120653 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Scanr1Sym2 (a6989586621681120652 :: (~>) a ((~>) a a)) (a6989586621681120653 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanr1Sym2 a6989586621681120652 a6989586621681120653 = Scanr1 a6989586621681120652 a6989586621681120653 |
data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) Source #
Instances
| SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing TransposeSym0 # | |
| 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) (a6989586621681120350 :: NonEmpty (NonEmpty a)) Source # | |
type family TransposeSym1 (a6989586621681120350 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| TransposeSym1 a6989586621681120350 = Transpose a6989586621681120350 |
data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing SortBySym0 # | |
| 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) (a6989586621681120342 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data SortBySym1 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) :: (~>) (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 a6989586621681120342 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SortBySym1 a6989586621681120342 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120343 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SortBySym2 (a6989586621681120342 :: (~>) a ((~>) a Ordering)) (a6989586621681120343 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortBySym2 a6989586621681120342 a6989586621681120343 = SortBy a6989586621681120342 a6989586621681120343 |
data SortWithSym0 :: (~>) ((~>) a o) ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing SortWithSym0 # | |
| 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) (a6989586621681120333 :: a ~> o) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120333 :: a ~> o) = SortWithSym1 a6989586621681120333 | |
data SortWithSym1 (a6989586621681120333 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| (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 a6989586621681120333 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SortWithSym1 a6989586621681120333 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120334 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SortWithSym2 (a6989586621681120333 :: (~>) a o) (a6989586621681120334 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortWithSym2 a6989586621681120333 a6989586621681120334 = SortWith a6989586621681120333 a6989586621681120334 |
data LengthSym0 :: (~>) (NonEmpty a) Nat Source #
Instances
| SingI (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing LengthSym0 # | |
| SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (LengthSym0 :: TyFun (NonEmpty a) Nat -> Type) (a6989586621681120843 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family LengthSym1 (a6989586621681120843 :: NonEmpty a) :: Nat where ... Source #
Equations
| LengthSym1 a6989586621681120843 = Length a6989586621681120843 |
data HeadSym0 :: (~>) (NonEmpty a) a Source #
Instances
| SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120778 :: NonEmpty a) Source # | |
data TailSym0 :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120774 :: NonEmpty a) Source # | |
data LastSym0 :: (~>) (NonEmpty a) a Source #
Instances
| SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621681120769 :: NonEmpty a) Source # | |
data InitSym0 :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120764 :: NonEmpty a) Source # | |
data (<|@#@$) :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120757 :: a) Source # | |
data (<|@#@$$) (a6989586621681120757 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((<|@#@$$) a6989586621681120757 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((<|@#@$$) a6989586621681120757 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120758 :: NonEmpty a) Source # | |
type family (a6989586621681120757 :: a) <|@#@$$$ (a6989586621681120758 :: NonEmpty a) :: NonEmpty a where ... Source #
data ConsSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120750 :: a) Source # | |
data ConsSym1 (a6989586621681120750 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ConsSym1 a6989586621681120750 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConsSym1 a6989586621681120750 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120751 :: NonEmpty a) Source # | |
type family ConsSym2 (a6989586621681120750 :: a) (a6989586621681120751 :: NonEmpty a) :: NonEmpty a where ... Source #
data UnconsSym0 :: (~>) (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 Methods sing :: Sing UnconsSym0 # | |
| 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) (a6989586621681120807 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family UnconsSym1 (a6989586621681120807 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #
Equations
| UnconsSym1 a6989586621681120807 = Uncons a6989586621681120807 |
data UnfoldrSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b)) Source #
Instances
| SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing UnfoldrSym0 # | |
| 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) (a6989586621681120783 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data UnfoldrSym1 (a6989586621681120783 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #
Instances
| SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldrSym1 d) # | |
| SuppressUnusedWarnings (UnfoldrSym1 a6989586621681120783 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621681120783 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120784 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family UnfoldrSym2 (a6989586621681120783 :: (~>) a (b, Maybe a)) (a6989586621681120784 :: a) :: NonEmpty b where ... Source #
Equations
| UnfoldrSym2 a6989586621681120783 a6989586621681120784 = Unfoldr a6989586621681120783 a6989586621681120784 |
data SortSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120741 :: NonEmpty a) Source # | |
data ReverseSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing ReverseSym0 # | |
| 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) (a6989586621681120636 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ReverseSym1 (a6989586621681120636 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| ReverseSym1 a6989586621681120636 = Reverse a6989586621681120636 |
data InitsSym0 :: (~>) [a] (NonEmpty [a]) Source #
Instances
| SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120708 :: [a]) Source # | |
data TailsSym0 :: (~>) [a] (NonEmpty [a]) Source #
Instances
| SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621681120702 :: [a]) Source # | |
data UnfoldSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b)) Source #
Instances
| SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing UnfoldSym0 # | |
| 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) (a6989586621681120818 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data UnfoldSym1 (a6989586621681120818 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #
Instances
| SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldSym1 d) # | |
| SuppressUnusedWarnings (UnfoldSym1 a6989586621681120818 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldSym1 a6989586621681120818 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120819 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data InsertSym0 :: (~>) a ((~>) [a] (NonEmpty a)) Source #
Instances
| SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing InsertSym0 # | |
| 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) (a6989586621681120694 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681120694 :: a) = InsertSym1 a6989586621681120694 | |
data InsertSym1 (a6989586621681120694 :: a) :: (~>) [a] (NonEmpty a) Source #
Instances
| (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 a6989586621681120694 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621681120694 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120695 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family InsertSym2 (a6989586621681120694 :: a) (a6989586621681120695 :: [a]) :: NonEmpty a where ... Source #
Equations
| InsertSym2 a6989586621681120694 a6989586621681120695 = Insert a6989586621681120694 a6989586621681120695 |
data TakeSym0 :: (~>) Nat ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120628 :: Nat) Source # | |
data TakeSym1 (a6989586621681120628 :: Nat) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621681120628 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120629 :: NonEmpty a) Source # | |
type family TakeSym2 (a6989586621681120628 :: Nat) (a6989586621681120629 :: NonEmpty a) :: [a] where ... Source #
data DropSym0 :: (~>) Nat ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym0 :: TyFun Nat (NonEmpty a ~> [a]) -> Type) (a6989586621681120619 :: Nat) Source # | |
data DropSym1 (a6989586621681120619 :: Nat) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621681120619 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120620 :: NonEmpty a) Source # | |
type family DropSym2 (a6989586621681120619 :: Nat) (a6989586621681120620 :: NonEmpty a) :: [a] where ... Source #
data SplitAtSym0 :: (~>) Nat ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing SplitAtSym0 # | |
| SuppressUnusedWarnings (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym0 :: TyFun Nat (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120610 :: Nat) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data SplitAtSym1 (a6989586621681120610 :: Nat) :: (~>) (NonEmpty a) ([a], [a]) Source #
Instances
| SingI d => SingI (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (SplitAtSym1 d) # | |
| SuppressUnusedWarnings (SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621681120610 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120611 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SplitAtSym2 (a6989586621681120610 :: Nat) (a6989586621681120611 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621681120610 a6989586621681120611 = SplitAt a6989586621681120610 a6989586621681120611 |
data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing TakeWhileSym0 # | |
| 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) (a6989586621681120601 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data TakeWhileSym1 (a6989586621681120601 :: (~>) a Bool) :: (~>) (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 a6989586621681120601 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeWhileSym1 a6989586621681120601 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120602 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family TakeWhileSym2 (a6989586621681120601 :: (~>) a Bool) (a6989586621681120602 :: NonEmpty a) :: [a] where ... Source #
Equations
| TakeWhileSym2 a6989586621681120601 a6989586621681120602 = TakeWhile a6989586621681120601 a6989586621681120602 |
data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing DropWhileSym0 # | |
| 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) (a6989586621681120592 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data DropWhileSym1 (a6989586621681120592 :: (~>) a Bool) :: (~>) (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 a6989586621681120592 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileSym1 a6989586621681120592 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120593 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family DropWhileSym2 (a6989586621681120592 :: (~>) a Bool) (a6989586621681120593 :: NonEmpty a) :: [a] where ... Source #
Equations
| DropWhileSym2 a6989586621681120592 a6989586621681120593 = DropWhile a6989586621681120592 a6989586621681120593 |
data SpanSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120583 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621681120583 :: (~>) a Bool) :: (~>) (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 a6989586621681120583 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SpanSym1 a6989586621681120583 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120584 :: NonEmpty a) Source # | |
type family SpanSym2 (a6989586621681120583 :: (~>) a Bool) (a6989586621681120584 :: NonEmpty a) :: ([a], [a]) where ... Source #
data BreakSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120574 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621681120574 :: (~>) a Bool) :: (~>) (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 a6989586621681120574 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (BreakSym1 a6989586621681120574 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120575 :: NonEmpty a) Source # | |
type family BreakSym2 (a6989586621681120574 :: (~>) a Bool) (a6989586621681120575 :: NonEmpty a) :: ([a], [a]) where ... Source #
data FilterSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing FilterSym0 # | |
| 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) (a6989586621681120565 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data FilterSym1 (a6989586621681120565 :: (~>) a Bool) :: (~>) (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 a6989586621681120565 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FilterSym1 a6989586621681120565 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120566 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family FilterSym2 (a6989586621681120565 :: (~>) a Bool) (a6989586621681120566 :: NonEmpty a) :: [a] where ... Source #
Equations
| FilterSym2 a6989586621681120565 a6989586621681120566 = Filter a6989586621681120565 a6989586621681120566 |
data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing PartitionSym0 # | |
| 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) (a6989586621681120556 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data PartitionSym1 (a6989586621681120556 :: (~>) a Bool) :: (~>) (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 a6989586621681120556 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (PartitionSym1 a6989586621681120556 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120557 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family PartitionSym2 (a6989586621681120556 :: (~>) a Bool) (a6989586621681120557 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 a6989586621681120556 a6989586621681120557 = Partition a6989586621681120556 a6989586621681120557 |
data GroupSym0 :: (~>) [a] [NonEmpty a] Source #
Instances
| SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120549 :: [a]) Source # | |
data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [NonEmpty a]) Source #
Instances
| SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing GroupBySym0 # | |
| 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) (a6989586621681120516 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data GroupBySym1 (a6989586621681120516 :: (~>) a ((~>) a Bool)) :: (~>) [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 a6989586621681120516 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupBySym1 a6989586621681120516 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120517 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family GroupBySym2 (a6989586621681120516 :: (~>) a ((~>) a Bool)) (a6989586621681120517 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupBySym2 a6989586621681120516 a6989586621681120517 = GroupBy a6989586621681120516 a6989586621681120517 |
data GroupWithSym0 :: (~>) ((~>) 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 Methods sing :: Sing GroupWithSym0 # | |
| 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) (a6989586621681120507 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120507 :: a ~> b) = GroupWithSym1 a6989586621681120507 | |
data GroupWithSym1 (a6989586621681120507 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #
Instances
| (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 a6989586621681120507 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWithSym1 a6989586621681120507 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120508 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family GroupWithSym2 (a6989586621681120507 :: (~>) a b) (a6989586621681120508 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupWithSym2 a6989586621681120507 a6989586621681120508 = GroupWith a6989586621681120507 a6989586621681120508 |
data GroupAllWithSym0 :: (~>) ((~>) 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 Methods | |
| 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) (a6989586621681120498 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120498 :: a ~> b) = GroupAllWithSym1 a6989586621681120498 | |
data GroupAllWithSym1 (a6989586621681120498 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #
Instances
| (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 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWithSym1 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120499 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym1 a6989586621681120498 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120499 :: [a]) = GroupAllWith a6989586621681120498 a6989586621681120499 | |
type family GroupAllWithSym2 (a6989586621681120498 :: (~>) a b) (a6989586621681120499 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupAllWithSym2 a6989586621681120498 a6989586621681120499 = GroupAllWith a6989586621681120498 a6989586621681120499 |
data Group1Sym0 :: (~>) (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 Methods sing :: Sing Group1Sym0 # | |
| 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) (a6989586621681120491 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Group1Sym1 (a6989586621681120491 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Group1Sym1 a6989586621681120491 = Group1 a6989586621681120491 |
data GroupBy1Sym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
| SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing GroupBy1Sym0 # | |
| 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) (a6989586621681120464 :: a ~> (a ~> Bool)) Source # | |
data GroupBy1Sym1 (a6989586621681120464 :: (~>) a ((~>) a Bool)) :: (~>) (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 a6989586621681120464 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupBy1Sym1 a6989586621681120464 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120465 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family GroupBy1Sym2 (a6989586621681120464 :: (~>) a ((~>) a Bool)) (a6989586621681120465 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupBy1Sym2 a6989586621681120464 a6989586621681120465 = GroupBy1 a6989586621681120464 a6989586621681120465 |
data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
| SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing GroupWith1Sym0 # | |
| 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) (a6989586621681120457 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data GroupWith1Sym1 (a6989586621681120457 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #
Instances
| (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 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWith1Sym1 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120458 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym1 a6989586621681120457 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120458 :: NonEmpty a) = GroupWith1 a6989586621681120457 a6989586621681120458 | |
type family GroupWith1Sym2 (a6989586621681120457 :: (~>) a b) (a6989586621681120458 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupWith1Sym2 a6989586621681120457 a6989586621681120458 = GroupWith1 a6989586621681120457 a6989586621681120458 |
data GroupAllWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
| SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods | |
| 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) (a6989586621681120448 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data GroupAllWith1Sym1 (a6989586621681120448 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #
Instances
| (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 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWith1Sym1 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120449 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym1 a6989586621681120448 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120449 :: NonEmpty a) = GroupAllWith1 a6989586621681120448 a6989586621681120449 | |
type family GroupAllWith1Sym2 (a6989586621681120448 :: (~>) a b) (a6989586621681120449 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupAllWith1Sym2 a6989586621681120448 a6989586621681120449 = GroupAllWith1 a6989586621681120448 a6989586621681120449 |
data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool) Source #
Instances
| SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing IsPrefixOfSym0 # | |
| 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) (a6989586621681120437 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681120437 :: [a]) = IsPrefixOfSym1 a6989586621681120437 | |
data IsPrefixOfSym1 (a6989586621681120437 :: [a]) :: (~>) (NonEmpty a) Bool Source #
Instances
| (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 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120438 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym1 a6989586621681120437 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120438 :: NonEmpty a) = IsPrefixOf a6989586621681120437 a6989586621681120438 | |
type family IsPrefixOfSym2 (a6989586621681120437 :: [a]) (a6989586621681120438 :: NonEmpty a) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 a6989586621681120437 a6989586621681120438 = IsPrefixOf a6989586621681120437 a6989586621681120438 |
data NubSym0 :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120368 :: NonEmpty a) Source # | |
data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120355 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621681120355 :: (~>) a ((~>) a Bool)) :: (~>) (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 a6989586621681120355 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NubBySym1 a6989586621681120355 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120356 :: NonEmpty a) Source # | |
type family NubBySym2 (a6989586621681120355 :: (~>) a ((~>) a Bool)) (a6989586621681120356 :: NonEmpty a) :: NonEmpty a where ... Source #
data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Nat a) Source #
Instances
| SingI ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Nat ~> a) -> Type) (a6989586621681120418 :: NonEmpty a) Source # | |
data (!!@#@$$) (a6989586621681120418 :: NonEmpty a) :: (~>) Nat a Source #
Instances
| SingI d => SingI ((!!@#@$$) d :: TyFun Nat a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621681120418 :: TyFun Nat a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621681120418 :: TyFun Nat a -> Type) (a6989586621681120419 :: Nat) Source # | |
type family (a6989586621681120418 :: NonEmpty a) !!@#@$$$ (a6989586621681120419 :: Nat) :: a where ... Source #
data ZipSym0 :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty (a, b))) Source #
Instances
| SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120409 :: NonEmpty a) Source # | |
data ZipSym1 (a6989586621681120409 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b)) Source #
Instances
| SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621681120409 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681120410 :: NonEmpty b) Source # | |
type family ZipSym2 (a6989586621681120409 :: NonEmpty a) (a6989586621681120410 :: NonEmpty b) :: NonEmpty (a, b) where ... Source #
data ZipWithSym0 :: (~>) ((~>) 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 # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing ZipWithSym0 # | |
| 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) (a6989586621681120398 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data ZipWithSym1 (a6989586621681120398 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)) Source #
Instances
| 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 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120399 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym1 a6989586621681120398 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120399 :: NonEmpty a) = ZipWithSym2 a6989586621681120398 a6989586621681120399 | |
data ZipWithSym2 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c) Source #
Instances
| (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 a6989586621681120398 a6989586621681120399 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621681120398 a6989586621681120399 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681120400 :: NonEmpty b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ZipWithSym3 (a6989586621681120398 :: (~>) a ((~>) b c)) (a6989586621681120399 :: NonEmpty a) (a6989586621681120400 :: NonEmpty b) :: NonEmpty c where ... Source #
Equations
| ZipWithSym3 a6989586621681120398 a6989586621681120399 a6989586621681120400 = ZipWith a6989586621681120398 a6989586621681120399 a6989586621681120400 |
data UnzipSym0 :: (~>) (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) Source #
Instances
| SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| 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) (a6989586621681120372 :: NonEmpty (a, b)) Source # | |
type family UnzipSym1 (a6989586621681120372 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #
data FromListSym0 :: (~>) [a] (NonEmpty a) Source #
Instances
| SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing FromListSym0 # | |
| SuppressUnusedWarnings (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120734 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family FromListSym1 (a6989586621681120734 :: [a]) :: NonEmpty a where ... Source #
Equations
| FromListSym1 a6989586621681120734 = FromList a6989586621681120734 |
data ToListSym0 :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing ToListSym0 # | |
| SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120729 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ToListSym1 (a6989586621681120729 :: NonEmpty a) :: [a] where ... Source #
Equations
| ToListSym1 a6989586621681120729 = ToList a6989586621681120729 |
data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a)) Source #
Instances
| SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing NonEmpty_Sym0 # | |
| 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) (a6989586621681120812 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family NonEmpty_Sym1 (a6989586621681120812 :: [a]) :: Maybe (NonEmpty a) where ... Source #
Equations
| NonEmpty_Sym1 a6989586621681120812 = NonEmpty_ a6989586621681120812 |
data XorSym0 :: (~>) (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 (a6989586621681120832 :: NonEmpty Bool) Source # | |
Orphan instances
| SMonadZip NonEmpty Source # | |
Methods sMzip :: forall a b (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply MzipSym0 t) t) Source # sMzipWith :: forall a b c (t :: a ~> (b ~> c)) (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply MzipWithSym0 t) t) t) Source # sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply MunzipSym0 t) Source # | |
| PMonadZip NonEmpty Source # | |