| Copyright | (C) 2016 Richard Eisenberg |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| 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) :: Natural where ...
- sLength :: forall a (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Natural)
- 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 :: Natural) (a :: NonEmpty a) :: [a] where ...
- sTake :: forall a (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a])
- type family Drop (a :: Natural) (a :: NonEmpty a) :: [a] where ...
- sDrop :: forall a (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a])
- type family SplitAt (a :: Natural) (a :: NonEmpty a) :: ([a], [a]) where ...
- sSplitAt :: forall a (t :: Natural) (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 :: Natural) :: a where ...
- (%!!) :: forall a (t :: NonEmpty a) (t :: Natural). 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 (:|@#@$$) (a6989586621679042179 :: a) :: (~>) [a] (NonEmpty (a :: Type))
- type family (a6989586621679042179 :: a) :|@#@$$$ (a6989586621679042180 :: [a]) :: NonEmpty (a :: Type) where ...
- data MapSym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty b))
- data MapSym1 (a6989586621681170428 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b)
- type family MapSym2 (a6989586621681170428 :: (~>) a b) (a6989586621681170429 :: NonEmpty a) :: NonEmpty b where ...
- data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data IntersperseSym1 (a6989586621681170356 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family IntersperseSym2 (a6989586621681170356 :: a) (a6989586621681170357 :: NonEmpty a) :: NonEmpty a where ...
- data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanlSym1 (a6989586621681170398 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanlSym2 (a6989586621681170398 :: (~>) b ((~>) a b)) (a6989586621681170399 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanlSym3 (a6989586621681170398 :: (~>) b ((~>) a b)) (a6989586621681170399 :: b) (a6989586621681170400 :: [a]) :: NonEmpty b where ...
- data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanrSym1 (a6989586621681170386 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanrSym2 (a6989586621681170386 :: (~>) a ((~>) b b)) (a6989586621681170387 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanrSym3 (a6989586621681170386 :: (~>) a ((~>) b b)) (a6989586621681170387 :: b) (a6989586621681170388 :: [a]) :: NonEmpty b where ...
- data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanl1Sym1 (a6989586621681170375 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanl1Sym2 (a6989586621681170375 :: (~>) a ((~>) a a)) (a6989586621681170376 :: NonEmpty a) :: NonEmpty a where ...
- data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanr1Sym1 (a6989586621681170367 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanr1Sym2 (a6989586621681170367 :: (~>) a ((~>) a a)) (a6989586621681170368 :: NonEmpty a) :: NonEmpty a where ...
- data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a))
- type family TransposeSym1 (a6989586621681170065 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (NonEmpty a) (NonEmpty a))
- data SortBySym1 (a6989586621681170057 :: (~>) a ((~>) a Ordering)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortBySym2 (a6989586621681170057 :: (~>) a ((~>) a Ordering)) (a6989586621681170058 :: NonEmpty a) :: NonEmpty a where ...
- data SortWithSym0 :: (~>) ((~>) a o) ((~>) (NonEmpty a) (NonEmpty a))
- data SortWithSym1 (a6989586621681170048 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortWithSym2 (a6989586621681170048 :: (~>) a o) (a6989586621681170049 :: NonEmpty a) :: NonEmpty a where ...
- data LengthSym0 :: (~>) (NonEmpty a) Natural
- type family LengthSym1 (a6989586621681170558 :: NonEmpty a) :: Natural where ...
- data HeadSym0 :: (~>) (NonEmpty a) a
- type family HeadSym1 (a6989586621681170493 :: NonEmpty a) :: a where ...
- data TailSym0 :: (~>) (NonEmpty a) [a]
- type family TailSym1 (a6989586621681170489 :: NonEmpty a) :: [a] where ...
- data LastSym0 :: (~>) (NonEmpty a) a
- type family LastSym1 (a6989586621681170484 :: NonEmpty a) :: a where ...
- data InitSym0 :: (~>) (NonEmpty a) [a]
- type family InitSym1 (a6989586621681170479 :: NonEmpty a) :: [a] where ...
- data (<|@#@$) :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data (<|@#@$$) (a6989586621681170472 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family (a6989586621681170472 :: a) <|@#@$$$ (a6989586621681170473 :: NonEmpty a) :: NonEmpty a where ...
- data ConsSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data ConsSym1 (a6989586621681170465 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family ConsSym2 (a6989586621681170465 :: a) (a6989586621681170466 :: NonEmpty a) :: NonEmpty a where ...
- data UnconsSym0 :: (~>) (NonEmpty a) (a, Maybe (NonEmpty a))
- type family UnconsSym1 (a6989586621681170522 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- data UnfoldrSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldrSym1 (a6989586621681170498 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- type family UnfoldrSym2 (a6989586621681170498 :: (~>) a (b, Maybe a)) (a6989586621681170499 :: a) :: NonEmpty b where ...
- data SortSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortSym1 (a6989586621681170456 :: NonEmpty a) :: NonEmpty a where ...
- data ReverseSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family ReverseSym1 (a6989586621681170351 :: NonEmpty a) :: NonEmpty a where ...
- data InitsSym0 :: (~>) [a] (NonEmpty [a])
- type family InitsSym1 (a6989586621681170423 :: [a]) :: NonEmpty [a] where ...
- data TailsSym0 :: (~>) [a] (NonEmpty [a])
- type family TailsSym1 (a6989586621681170417 :: [a]) :: NonEmpty [a] where ...
- data UnfoldSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldSym1 (a6989586621681170533 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- data InsertSym0 :: (~>) a ((~>) [a] (NonEmpty a))
- data InsertSym1 (a6989586621681170409 :: a) :: (~>) [a] (NonEmpty a)
- type family InsertSym2 (a6989586621681170409 :: a) (a6989586621681170410 :: [a]) :: NonEmpty a where ...
- data TakeSym0 :: (~>) Natural ((~>) (NonEmpty a) [a])
- data TakeSym1 (a6989586621681170343 :: Natural) :: (~>) (NonEmpty a) [a]
- type family TakeSym2 (a6989586621681170343 :: Natural) (a6989586621681170344 :: NonEmpty a) :: [a] where ...
- data DropSym0 :: (~>) Natural ((~>) (NonEmpty a) [a])
- data DropSym1 (a6989586621681170334 :: Natural) :: (~>) (NonEmpty a) [a]
- type family DropSym2 (a6989586621681170334 :: Natural) (a6989586621681170335 :: NonEmpty a) :: [a] where ...
- data SplitAtSym0 :: (~>) Natural ((~>) (NonEmpty a) ([a], [a]))
- data SplitAtSym1 (a6989586621681170325 :: Natural) :: (~>) (NonEmpty a) ([a], [a])
- type family SplitAtSym2 (a6989586621681170325 :: Natural) (a6989586621681170326 :: NonEmpty a) :: ([a], [a]) where ...
- data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data TakeWhileSym1 (a6989586621681170316 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family TakeWhileSym2 (a6989586621681170316 :: (~>) a Bool) (a6989586621681170317 :: NonEmpty a) :: [a] where ...
- data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data DropWhileSym1 (a6989586621681170307 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family DropWhileSym2 (a6989586621681170307 :: (~>) a Bool) (a6989586621681170308 :: NonEmpty a) :: [a] where ...
- data SpanSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data SpanSym1 (a6989586621681170298 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family SpanSym2 (a6989586621681170298 :: (~>) a Bool) (a6989586621681170299 :: NonEmpty a) :: ([a], [a]) where ...
- data BreakSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data BreakSym1 (a6989586621681170289 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family BreakSym2 (a6989586621681170289 :: (~>) a Bool) (a6989586621681170290 :: NonEmpty a) :: ([a], [a]) where ...
- data FilterSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data FilterSym1 (a6989586621681170280 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family FilterSym2 (a6989586621681170280 :: (~>) a Bool) (a6989586621681170281 :: NonEmpty a) :: [a] where ...
- data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data PartitionSym1 (a6989586621681170271 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family PartitionSym2 (a6989586621681170271 :: (~>) a Bool) (a6989586621681170272 :: NonEmpty a) :: ([a], [a]) where ...
- data GroupSym0 :: (~>) [a] [NonEmpty a]
- type family GroupSym1 (a6989586621681170264 :: [a]) :: [NonEmpty a] where ...
- data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [NonEmpty a])
- data GroupBySym1 (a6989586621681170231 :: (~>) a ((~>) a Bool)) :: (~>) [a] [NonEmpty a]
- type family GroupBySym2 (a6989586621681170231 :: (~>) a ((~>) a Bool)) (a6989586621681170232 :: [a]) :: [NonEmpty a] where ...
- data GroupWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupWithSym1 (a6989586621681170222 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupWithSym2 (a6989586621681170222 :: (~>) a b) (a6989586621681170223 :: [a]) :: [NonEmpty a] where ...
- data GroupAllWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupAllWithSym1 (a6989586621681170213 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupAllWithSym2 (a6989586621681170213 :: (~>) a b) (a6989586621681170214 :: [a]) :: [NonEmpty a] where ...
- data Group1Sym0 :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family Group1Sym1 (a6989586621681170206 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupBy1Sym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupBy1Sym1 (a6989586621681170179 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupBy1Sym2 (a6989586621681170179 :: (~>) a ((~>) a Bool)) (a6989586621681170180 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupWith1Sym1 (a6989586621681170172 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupWith1Sym2 (a6989586621681170172 :: (~>) a b) (a6989586621681170173 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupAllWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupAllWith1Sym1 (a6989586621681170163 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupAllWith1Sym2 (a6989586621681170163 :: (~>) a b) (a6989586621681170164 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool)
- data IsPrefixOfSym1 (a6989586621681170152 :: [a]) :: (~>) (NonEmpty a) Bool
- type family IsPrefixOfSym2 (a6989586621681170152 :: [a]) (a6989586621681170153 :: NonEmpty a) :: Bool where ...
- data NubSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubSym1 (a6989586621681170083 :: NonEmpty a) :: NonEmpty a where ...
- data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty a))
- data NubBySym1 (a6989586621681170070 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubBySym2 (a6989586621681170070 :: (~>) a ((~>) a Bool)) (a6989586621681170071 :: NonEmpty a) :: NonEmpty a where ...
- data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Natural a)
- data (!!@#@$$) (a6989586621681170133 :: NonEmpty a) :: (~>) Natural a
- type family (a6989586621681170133 :: NonEmpty a) !!@#@$$$ (a6989586621681170134 :: Natural) :: a where ...
- data ZipSym0 :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty (a, b)))
- data ZipSym1 (a6989586621681170124 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b))
- type family ZipSym2 (a6989586621681170124 :: NonEmpty a) (a6989586621681170125 :: NonEmpty b) :: NonEmpty (a, b) where ...
- data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)))
- data ZipWithSym1 (a6989586621681170113 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c))
- data ZipWithSym2 (a6989586621681170113 :: (~>) a ((~>) b c)) (a6989586621681170114 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c)
- type family ZipWithSym3 (a6989586621681170113 :: (~>) a ((~>) b c)) (a6989586621681170114 :: NonEmpty a) (a6989586621681170115 :: NonEmpty b) :: NonEmpty c where ...
- data UnzipSym0 :: (~>) (NonEmpty (a, b)) (NonEmpty a, NonEmpty b)
- type family UnzipSym1 (a6989586621681170087 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- data FromListSym0 :: (~>) [a] (NonEmpty a)
- type family FromListSym1 (a6989586621681170449 :: [a]) :: NonEmpty a where ...
- data ToListSym0 :: (~>) (NonEmpty a) [a]
- type family ToListSym1 (a6989586621681170444 :: NonEmpty a) :: [a] where ...
- data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a))
- type family NonEmpty_Sym1 (a6989586621681170527 :: [a]) :: Maybe (NonEmpty a) where ...
- data XorSym0 :: (~>) (NonEmpty Bool) Bool
- type family XorSym1 (a6989586621681170547 :: NonEmpty Bool) :: Bool where ...
The NonEmpty singleton
type family Sing :: k -> Type #
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_6989586621681170361 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 #
type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #
Equations
| Scanl f z a_6989586621681170392 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanlSym0 f) z)) a_6989586621681170392 |
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 #
type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: NonEmpty b where ... Source #
Equations
| Scanr f z a_6989586621681170380 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply ListscanrSym0 f) z)) a_6989586621681170380 |
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 #
type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanl1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply (Apply ListscanlSym0 f) a) as) |
sScanl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) Source #
type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanr1 f ('(:|) a as) = Apply FromListSym0 (Apply (Apply Listscanr1Sym0 f) (Apply (Apply (:@#@$) a) as)) |
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_6989586621681170061 = Apply (Apply (Apply (.@#@$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply (.@#@$) ListtransposeSym0) (Apply (Apply (.@#@$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621681170061 |
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 #
Equations
| SortBy f a_6989586621681170052 = Apply (Apply LiftSym0 (Apply ListsortBySym0 f)) a_6989586621681170052 |
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_6989586621681170041 a_6989586621681170043 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621681170041) a_6989586621681170043 |
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 #
type family Length (a :: NonEmpty a) :: Natural where ... Source #
Equations
| Length ('(:|) _ xs) = Apply (Apply (+@#@$) (FromInteger 1)) (Apply ListlengthSym0 xs) |
(%<|) :: 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_6989586621681170515 f a (Let6989586621681170513Scrutinee_6989586621681168939Sym2 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 #
type family Sort (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Sort a_6989586621681170452 = Apply (Apply LiftSym0 ListsortSym0) a_6989586621681170452 |
sSort :: forall a (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) Source #
type family Reverse (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Reverse a_6989586621681170347 = Apply (Apply LiftSym0 ListreverseSym0) a_6989586621681170347 |
type family Inits (a :: [a]) :: NonEmpty [a] where ... Source #
Equations
| Inits a_6989586621681170419 = Apply (Apply (Apply (.@#@$) FromListSym0) ListinitsSym0) a_6989586621681170419 |
type family Tails (a :: [a]) :: NonEmpty [a] where ... Source #
Equations
| Tails a_6989586621681170413 = Apply (Apply (Apply (.@#@$) FromListSym0) ListtailsSym0) a_6989586621681170413 |
type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #
Equations
| Unfold f a = Case_6989586621681170539 f a (Let6989586621681170537Scrutinee_6989586621681168929Sym2 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 #
type family Insert (a :: a) (a :: [a]) :: NonEmpty a where ... Source #
Equations
| Insert a a_6989586621681170404 = Apply (Apply (Apply (.@#@$) FromListSym0) (Apply ListinsertSym0 a)) a_6989586621681170404 |
sInsert :: forall a (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) Source #
type family Take (a :: Natural) (a :: NonEmpty a) :: [a] where ... Source #
Equations
| Take n a_6989586621681170338 = Apply (Apply (Apply (.@#@$) (Apply ListtakeSym0 n)) ToListSym0) a_6989586621681170338 |
sTake :: forall a (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) Source #
type family Drop (a :: Natural) (a :: NonEmpty a) :: [a] where ... Source #
Equations
| Drop n a_6989586621681170329 = Apply (Apply (Apply (.@#@$) (Apply ListdropSym0 n)) ToListSym0) a_6989586621681170329 |
sDrop :: forall a (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) Source #
type family SplitAt (a :: Natural) (a :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| SplitAt n a_6989586621681170320 = Apply (Apply (Apply (.@#@$) (Apply ListsplitAtSym0 n)) ToListSym0) a_6989586621681170320 |
sSplitAt :: forall a (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) Source #
type family TakeWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #
Equations
| TakeWhile p a_6989586621681170311 = Apply (Apply (Apply (.@#@$) (Apply ListtakeWhileSym0 p)) ToListSym0) a_6989586621681170311 |
sTakeWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) Source #
type family DropWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #
Equations
| DropWhile p a_6989586621681170302 = Apply (Apply (Apply (.@#@$) (Apply ListdropWhileSym0 p)) ToListSym0) a_6989586621681170302 |
sDropWhile :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) Source #
type family Span (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| Span p a_6989586621681170293 = Apply (Apply (Apply (.@#@$) (Apply ListspanSym0 p)) ToListSym0) a_6989586621681170293 |
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 #
type family Filter (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ... Source #
Equations
| Filter p a_6989586621681170275 = Apply (Apply (Apply (.@#@$) (Apply ListfilterSym0 p)) ToListSym0) a_6989586621681170275 |
sFilter :: forall a (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) Source #
type family Partition (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| Partition p a_6989586621681170266 = Apply (Apply (Apply (.@#@$) (Apply ListpartitionSym0 p)) ToListSym0) a_6989586621681170266 |
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_6989586621681170260 = Apply (Apply GroupBySym0 (==@#@$)) a_6989586621681170260 |
type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupBy eq0 a_6989586621681170226 = Apply (Apply (Let6989586621681170235GoSym2 eq0 a_6989586621681170226) eq0) a_6989586621681170226 |
sGroupBy :: forall a (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a]) Source #
type family GroupWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupWith f a_6989586621681170217 = Apply (Apply GroupBySym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681170217 |
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_6989586621681170208 = Apply (Apply (Apply (.@#@$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621681170208 |
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_6989586621681170202 = Apply (Apply GroupBy1Sym0 (==@#@$)) a_6989586621681170202 |
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 #
Equations
| GroupBy1 eq ('(:|) x xs) = Apply (Apply (:|@#@$) (Apply (Apply (:|@#@$) x) (Let6989586621681170184YsSym3 eq x xs))) (Apply (Apply GroupBySym0 eq) (Let6989586621681170184ZsSym3 eq x xs)) |
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_6989586621681170167 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621681170167 |
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_6989586621681170158 = Apply (Apply (Apply (.@#@$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621681170158 |
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 #
Equations
| IsPrefixOf '[] _ = TrueSym0 | |
| IsPrefixOf ('(:) y ys) ('(:|) x xs) = Apply (Apply (&&@#@$) (Apply (Apply (==@#@$) y) x)) (Apply (Apply ListisPrefixOfSym0 ys) xs) |
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 :: Natural) :: a where ... Source #
Equations
| arg_6989586621681168951 !! arg_6989586621681168953 = Case_6989586621681170137 arg_6989586621681168951 arg_6989586621681168953 (Apply (Apply Tuple2Sym0 arg_6989586621681168951) arg_6989586621681168953) |
(%!!) :: forall a (t :: NonEmpty a) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) Source #
type family Zip (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty (a, b) where ... Source #
Equations
| Zip ('(:|) x xs) ('(:|) y ys) = Apply (Apply (:|@#@$) (Apply (Apply Tuple2Sym0 x) y)) (Apply (Apply ListzipSym0 xs) ys) |
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 #
type family Unzip (a :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ... Source #
Equations
| Unzip ('(:|) '(a, b) asbs) = Apply (Apply Tuple2Sym0 (Apply (Apply (:|@#@$) a) (Let6989586621681170091AsSym3 a b asbs))) (Apply (Apply (:|@#@$) b) (Let6989586621681170091BsSym3 a b asbs)) |
sUnzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) Source #
type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ... Source #
Equations
| NonEmpty_ '[] = NothingSym0 | |
| NonEmpty_ ('(:) a as) = Apply JustSym0 (Apply (Apply (:|@#@$) a) as) |
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) (a6989586621679042179 :: a) Source # | |
Defined in Data.Singletons.Base.Instances | |
data (:|@#@$$) (a6989586621679042179 :: a) :: (~>) [a] (NonEmpty (a :: Type)) infixr 5 Source #
Instances
| SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:|@#@$$) a6989586621679042179 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:|@#@$$) a6989586621679042179 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679042180 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances | |
type family (a6989586621679042179 :: a) :|@#@$$$ (a6989586621679042180 :: [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) (a6989586621681170428 :: a ~> b) Source # | |
data MapSym1 (a6989586621681170428 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b) Source #
Instances
| SingI1 (MapSym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621681170428 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621681170428 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681170429 :: NonEmpty a) Source # | |
type family MapSym2 (a6989586621681170428 :: (~>) a b) (a6989586621681170429 :: 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 | |
| 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) (a6989586621681170356 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681170356 :: a) = IntersperseSym1 a6989586621681170356 | |
data IntersperseSym1 (a6989586621681170356 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI1 (IntersperseSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (IntersperseSym1 x) | |
| SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (IntersperseSym1 d) | |
| SuppressUnusedWarnings (IntersperseSym1 a6989586621681170356 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621681170356 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170357 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym1 a6989586621681170356 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170357 :: NonEmpty a) = Intersperse a6989586621681170356 a6989586621681170357 | |
type family IntersperseSym2 (a6989586621681170356 :: a) (a6989586621681170357 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| IntersperseSym2 a6989586621681170356 a6989586621681170357 = Intersperse a6989586621681170356 a6989586621681170357 |
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) (a6989586621681170398 :: b ~> (a ~> b)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data ScanlSym1 (a6989586621681170398 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621681170398 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621681170398 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681170399 :: b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data ScanlSym2 (a6989586621681170398 :: (~>) b ((~>) a b)) (a6989586621681170399 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym2 a6989586621681170398 a6989586621681170399 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621681170398 a6989586621681170399 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681170400 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ScanlSym3 (a6989586621681170398 :: (~>) b ((~>) a b)) (a6989586621681170399 :: b) (a6989586621681170400 :: [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) (a6989586621681170386 :: a ~> (b ~> b)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data ScanrSym1 (a6989586621681170386 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621681170386 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621681170386 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681170387 :: b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
data ScanrSym2 (a6989586621681170386 :: (~>) a ((~>) b b)) (a6989586621681170387 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym2 a6989586621681170386 a6989586621681170387 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621681170386 a6989586621681170387 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681170388 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ScanrSym3 (a6989586621681170386 :: (~>) a ((~>) b b)) (a6989586621681170387 :: b) (a6989586621681170388 :: [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) (a6989586621681170375 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681170375 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621681170375 | |
data Scanl1Sym1 (a6989586621681170375 :: (~>) 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 a6989586621681170375 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Scanl1Sym1 x) | |
| type Apply (Scanl1Sym1 a6989586621681170375 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170376 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Scanl1Sym2 (a6989586621681170375 :: (~>) a ((~>) a a)) (a6989586621681170376 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanl1Sym2 a6989586621681170375 a6989586621681170376 = Scanl1 a6989586621681170375 a6989586621681170376 |
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) (a6989586621681170367 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681170367 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621681170367 | |
data Scanr1Sym1 (a6989586621681170367 :: (~>) 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 a6989586621681170367 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (Scanr1Sym1 x) | |
| type Apply (Scanr1Sym1 a6989586621681170367 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170368 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Scanr1Sym2 (a6989586621681170367 :: (~>) a ((~>) a a)) (a6989586621681170368 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanr1Sym2 a6989586621681170367 a6989586621681170368 = Scanr1 a6989586621681170367 a6989586621681170368 |
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 | |
| 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) (a6989586621681170065 :: NonEmpty (NonEmpty a)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family TransposeSym1 (a6989586621681170065 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| TransposeSym1 a6989586621681170065 = Transpose a6989586621681170065 |
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) (a6989586621681170057 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681170057 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621681170057 | |
data SortBySym1 (a6989586621681170057 :: (~>) 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 a6989586621681170057 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (SortBySym1 x) | |
| type Apply (SortBySym1 a6989586621681170057 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170058 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SortBySym2 (a6989586621681170057 :: (~>) a ((~>) a Ordering)) (a6989586621681170058 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortBySym2 a6989586621681170057 a6989586621681170058 = SortBy a6989586621681170057 a6989586621681170058 |
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) (a6989586621681170048 :: a ~> o) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681170048 :: a ~> o) = SortWithSym1 a6989586621681170048 | |
data SortWithSym1 (a6989586621681170048 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SOrd o => SingI1 (SortWithSym1 :: (a ~> o) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (SortWithSym1 x) | |
| (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 a6989586621681170048 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SortWithSym1 a6989586621681170048 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170049 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SortWithSym2 (a6989586621681170048 :: (~>) a o) (a6989586621681170049 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortWithSym2 a6989586621681170048 a6989586621681170049 = SortWith a6989586621681170048 a6989586621681170049 |
data LengthSym0 :: (~>) (NonEmpty a) Natural Source #
Instances
| SingI (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing LengthSym0 | |
| SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621681170558 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family LengthSym1 (a6989586621681170558 :: NonEmpty a) :: Natural where ... Source #
Equations
| LengthSym1 a6989586621681170558 = Length a6989586621681170558 |
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) (a6989586621681170493 :: 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) (a6989586621681170489 :: 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) (a6989586621681170484 :: 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) (a6989586621681170479 :: 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) (a6989586621681170472 :: a) Source # | |
data (<|@#@$$) (a6989586621681170472 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI1 ((<|@#@$$) :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((<|@#@$$) a6989586621681170472 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((<|@#@$$) a6989586621681170472 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170473 :: NonEmpty a) Source # | |
type family (a6989586621681170472 :: a) <|@#@$$$ (a6989586621681170473 :: 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) (a6989586621681170465 :: a) Source # | |
data ConsSym1 (a6989586621681170465 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ConsSym1 a6989586621681170465 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConsSym1 a6989586621681170465 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170466 :: NonEmpty a) Source # | |
type family ConsSym2 (a6989586621681170465 :: a) (a6989586621681170466 :: 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) (a6989586621681170522 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family UnconsSym1 (a6989586621681170522 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #
Equations
| UnconsSym1 a6989586621681170522 = Uncons a6989586621681170522 |
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) (a6989586621681170498 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681170498 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621681170498 | |
data UnfoldrSym1 (a6989586621681170498 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #
Instances
| SingI1 (UnfoldrSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (UnfoldrSym1 x) | |
| SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldrSym1 d) | |
| SuppressUnusedWarnings (UnfoldrSym1 a6989586621681170498 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621681170498 :: TyFun a (NonEmpty b) -> Type) (a6989586621681170499 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldrSym1 a6989586621681170498 :: TyFun a (NonEmpty b) -> Type) (a6989586621681170499 :: a) = Unfoldr a6989586621681170498 a6989586621681170499 | |
type family UnfoldrSym2 (a6989586621681170498 :: (~>) a (b, Maybe a)) (a6989586621681170499 :: a) :: NonEmpty b where ... Source #
Equations
| UnfoldrSym2 a6989586621681170498 a6989586621681170499 = Unfoldr a6989586621681170498 a6989586621681170499 |
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) (a6989586621681170456 :: 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) (a6989586621681170351 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ReverseSym1 (a6989586621681170351 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| ReverseSym1 a6989586621681170351 = Reverse a6989586621681170351 |
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) (a6989586621681170423 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621681170417 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621681170533 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681170533 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621681170533 | |
data UnfoldSym1 (a6989586621681170533 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b) Source #
Instances
| SingI1 (UnfoldSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (UnfoldSym1 x) | |
| SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (UnfoldSym1 d) | |
| SuppressUnusedWarnings (UnfoldSym1 a6989586621681170533 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldSym1 a6989586621681170533 :: TyFun a (NonEmpty b) -> Type) (a6989586621681170534 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldSym1 a6989586621681170533 :: TyFun a (NonEmpty b) -> Type) (a6989586621681170534 :: a) = Unfold a6989586621681170533 a6989586621681170534 | |
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) (a6989586621681170409 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621681170409 :: a) = InsertSym1 a6989586621681170409 | |
data InsertSym1 (a6989586621681170409 :: a) :: (~>) [a] (NonEmpty a) Source #
Instances
| SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (InsertSym1 x) | |
| (SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (InsertSym1 d) | |
| SuppressUnusedWarnings (InsertSym1 a6989586621681170409 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621681170409 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681170410 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym1 a6989586621681170409 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681170410 :: [a]) = Insert a6989586621681170409 a6989586621681170410 | |
type family InsertSym2 (a6989586621681170409 :: a) (a6989586621681170410 :: [a]) :: NonEmpty a where ... Source #
Equations
| InsertSym2 a6989586621681170409 a6989586621681170410 = Insert a6989586621681170409 a6989586621681170410 |
data TakeSym0 :: (~>) Natural ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621681170343 :: Natural) Source # | |
data TakeSym1 (a6989586621681170343 :: Natural) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TakeSym1 a6989586621681170343 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621681170343 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170344 :: NonEmpty a) Source # | |
type family TakeSym2 (a6989586621681170343 :: Natural) (a6989586621681170344 :: NonEmpty a) :: [a] where ... Source #
data DropSym0 :: (~>) Natural ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621681170334 :: Natural) Source # | |
data DropSym1 (a6989586621681170334 :: Natural) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (DropSym1 a6989586621681170334 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621681170334 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170335 :: NonEmpty a) Source # | |
type family DropSym2 (a6989586621681170334 :: Natural) (a6989586621681170335 :: NonEmpty a) :: [a] where ... Source #
data SplitAtSym0 :: (~>) Natural ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing SplitAtSym0 | |
| SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681170325 :: Natural) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681170325 :: Natural) = SplitAtSym1 a6989586621681170325 :: TyFun (NonEmpty a) ([a], [a]) -> Type | |
data SplitAtSym1 (a6989586621681170325 :: Natural) :: (~>) (NonEmpty a) ([a], [a]) Source #
Instances
| SingI1 (SplitAtSym1 :: Natural -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (SplitAtSym1 x) | |
| 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 a6989586621681170325 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621681170325 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170326 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SplitAtSym1 a6989586621681170325 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170326 :: NonEmpty a) = SplitAt a6989586621681170325 a6989586621681170326 | |
type family SplitAtSym2 (a6989586621681170325 :: Natural) (a6989586621681170326 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621681170325 a6989586621681170326 = SplitAt a6989586621681170325 a6989586621681170326 |
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 | |
| 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) (a6989586621681170316 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681170316 :: a ~> Bool) = TakeWhileSym1 a6989586621681170316 | |
data TakeWhileSym1 (a6989586621681170316 :: (~>) 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 a6989586621681170316 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (TakeWhileSym1 x) | |
| type Apply (TakeWhileSym1 a6989586621681170316 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170317 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (TakeWhileSym1 a6989586621681170316 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170317 :: NonEmpty a) = TakeWhile a6989586621681170316 a6989586621681170317 | |
type family TakeWhileSym2 (a6989586621681170316 :: (~>) a Bool) (a6989586621681170317 :: NonEmpty a) :: [a] where ... Source #
Equations
| TakeWhileSym2 a6989586621681170316 a6989586621681170317 = TakeWhile a6989586621681170316 a6989586621681170317 |
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 | |
| 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) (a6989586621681170307 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681170307 :: a ~> Bool) = DropWhileSym1 a6989586621681170307 | |
data DropWhileSym1 (a6989586621681170307 :: (~>) 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 a6989586621681170307 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (DropWhileSym1 x) | |
| type Apply (DropWhileSym1 a6989586621681170307 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170308 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (DropWhileSym1 a6989586621681170307 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170308 :: NonEmpty a) = DropWhile a6989586621681170307 a6989586621681170308 | |
type family DropWhileSym2 (a6989586621681170307 :: (~>) a Bool) (a6989586621681170308 :: NonEmpty a) :: [a] where ... Source #
Equations
| DropWhileSym2 a6989586621681170307 a6989586621681170308 = DropWhile a6989586621681170307 a6989586621681170308 |
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) (a6989586621681170298 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621681170298 :: (~>) 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 a6989586621681170298 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| type Apply (SpanSym1 a6989586621681170298 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170299 :: NonEmpty a) Source # | |
type family SpanSym2 (a6989586621681170298 :: (~>) a Bool) (a6989586621681170299 :: 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) (a6989586621681170289 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621681170289 :: (~>) 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 a6989586621681170289 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| type Apply (BreakSym1 a6989586621681170289 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170290 :: NonEmpty a) Source # | |
type family BreakSym2 (a6989586621681170289 :: (~>) a Bool) (a6989586621681170290 :: 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) (a6989586621681170280 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681170280 :: a ~> Bool) = FilterSym1 a6989586621681170280 | |
data FilterSym1 (a6989586621681170280 :: (~>) 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 a6989586621681170280 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (FilterSym1 x) | |
| type Apply (FilterSym1 a6989586621681170280 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170281 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FilterSym1 a6989586621681170280 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170281 :: NonEmpty a) = Filter a6989586621681170280 a6989586621681170281 | |
type family FilterSym2 (a6989586621681170280 :: (~>) a Bool) (a6989586621681170281 :: NonEmpty a) :: [a] where ... Source #
Equations
| FilterSym2 a6989586621681170280 a6989586621681170281 = Filter a6989586621681170280 a6989586621681170281 |
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 | |
| 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) (a6989586621681170271 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681170271 :: a ~> Bool) = PartitionSym1 a6989586621681170271 | |
data PartitionSym1 (a6989586621681170271 :: (~>) 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 a6989586621681170271 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (PartitionSym1 x) | |
| type Apply (PartitionSym1 a6989586621681170271 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170272 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (PartitionSym1 a6989586621681170271 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681170272 :: NonEmpty a) = Partition a6989586621681170271 a6989586621681170272 | |
type family PartitionSym2 (a6989586621681170271 :: (~>) a Bool) (a6989586621681170272 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 a6989586621681170271 a6989586621681170272 = Partition a6989586621681170271 a6989586621681170272 |
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) (a6989586621681170264 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621681170231 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681170231 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621681170231 | |
data GroupBySym1 (a6989586621681170231 :: (~>) 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 a6989586621681170231 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupBySym1 x) | |
| type Apply (GroupBySym1 a6989586621681170231 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170232 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBySym1 a6989586621681170231 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170232 :: [a]) = GroupBy a6989586621681170231 a6989586621681170232 | |
type family GroupBySym2 (a6989586621681170231 :: (~>) a ((~>) a Bool)) (a6989586621681170232 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupBySym2 a6989586621681170231 a6989586621681170232 = GroupBy a6989586621681170231 a6989586621681170232 |
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 | |
| 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) (a6989586621681170222 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681170222 :: a ~> b) = GroupWithSym1 a6989586621681170222 | |
data GroupWithSym1 (a6989586621681170222 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #
Instances
| SEq b => SingI1 (GroupWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupWithSym1 x) | |
| (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 a6989586621681170222 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWithSym1 a6989586621681170222 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170223 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym1 a6989586621681170222 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170223 :: [a]) = GroupWith a6989586621681170222 a6989586621681170223 | |
type family GroupWithSym2 (a6989586621681170222 :: (~>) a b) (a6989586621681170223 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupWithSym2 a6989586621681170222 a6989586621681170223 = GroupWith a6989586621681170222 a6989586621681170223 |
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) (a6989586621681170213 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681170213 :: a ~> b) = GroupAllWithSym1 a6989586621681170213 | |
data GroupAllWithSym1 (a6989586621681170213 :: (~>) a b) :: (~>) [a] [NonEmpty a] Source #
Instances
| SOrd b => SingI1 (GroupAllWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupAllWithSym1 x) | |
| (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 a6989586621681170213 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWithSym1 a6989586621681170213 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170214 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym1 a6989586621681170213 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681170214 :: [a]) = GroupAllWith a6989586621681170213 a6989586621681170214 | |
type family GroupAllWithSym2 (a6989586621681170213 :: (~>) a b) (a6989586621681170214 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupAllWithSym2 a6989586621681170213 a6989586621681170214 = GroupAllWith a6989586621681170213 a6989586621681170214 |
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) (a6989586621681170206 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family Group1Sym1 (a6989586621681170206 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Group1Sym1 a6989586621681170206 = Group1 a6989586621681170206 |
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) (a6989586621681170179 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681170179 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621681170179 | |
data GroupBy1Sym1 (a6989586621681170179 :: (~>) 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 a6989586621681170179 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (GroupBy1Sym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupBy1Sym1 x) | |
| type Apply (GroupBy1Sym1 a6989586621681170179 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681170180 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family GroupBy1Sym2 (a6989586621681170179 :: (~>) a ((~>) a Bool)) (a6989586621681170180 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupBy1Sym2 a6989586621681170179 a6989586621681170180 = GroupBy1 a6989586621681170179 a6989586621681170180 |
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 | |
| 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) (a6989586621681170172 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681170172 :: a ~> b) = GroupWith1Sym1 a6989586621681170172 | |
data GroupWith1Sym1 (a6989586621681170172 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #
Instances
| SEq b => SingI1 (GroupWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupWith1Sym1 x) | |
| (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 a6989586621681170172 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWith1Sym1 a6989586621681170172 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681170173 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym1 a6989586621681170172 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681170173 :: NonEmpty a) = GroupWith1 a6989586621681170172 a6989586621681170173 | |
type family GroupWith1Sym2 (a6989586621681170172 :: (~>) a b) (a6989586621681170173 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupWith1Sym2 a6989586621681170172 a6989586621681170173 = GroupWith1 a6989586621681170172 a6989586621681170173 |
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) (a6989586621681170163 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681170163 :: a ~> b) = GroupAllWith1Sym1 a6989586621681170163 | |
data GroupAllWith1Sym1 (a6989586621681170163 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a)) Source #
Instances
| SOrd b => SingI1 (GroupAllWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (GroupAllWith1Sym1 x) | |
| (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 a6989586621681170163 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWith1Sym1 a6989586621681170163 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681170164 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym1 a6989586621681170163 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681170164 :: NonEmpty a) = GroupAllWith1 a6989586621681170163 a6989586621681170164 | |
type family GroupAllWith1Sym2 (a6989586621681170163 :: (~>) a b) (a6989586621681170164 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupAllWith1Sym2 a6989586621681170163 a6989586621681170164 = GroupAllWith1 a6989586621681170163 a6989586621681170164 |
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 | |
| 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) (a6989586621681170152 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621681170152 :: [a]) = IsPrefixOfSym1 a6989586621681170152 | |
data IsPrefixOfSym1 (a6989586621681170152 :: [a]) :: (~>) (NonEmpty a) Bool Source #
Instances
| SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (IsPrefixOfSym1 x) | |
| (SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing (IsPrefixOfSym1 d) | |
| SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621681170152 :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621681170152 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681170153 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym1 a6989586621681170152 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681170153 :: NonEmpty a) = IsPrefixOf a6989586621681170152 a6989586621681170153 | |
type family IsPrefixOfSym2 (a6989586621681170152 :: [a]) (a6989586621681170153 :: NonEmpty a) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 a6989586621681170152 a6989586621681170153 = IsPrefixOf a6989586621681170152 a6989586621681170153 |
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) (a6989586621681170083 :: 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) (a6989586621681170070 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621681170070 :: (~>) 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 a6989586621681170070 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| type Apply (NubBySym1 a6989586621681170070 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681170071 :: NonEmpty a) Source # | |
type family NubBySym2 (a6989586621681170070 :: (~>) a ((~>) a Bool)) (a6989586621681170071 :: NonEmpty a) :: NonEmpty a where ... Source #
data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Natural a) Source #
Instances
| SingI ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621681170133 :: NonEmpty a) Source # | |
data (!!@#@$$) (a6989586621681170133 :: NonEmpty a) :: (~>) Natural a Source #
Instances
| SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621681170133 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621681170133 :: TyFun Natural a -> Type) (a6989586621681170134 :: Natural) Source # | |
type family (a6989586621681170133 :: NonEmpty a) !!@#@$$$ (a6989586621681170134 :: Natural) :: 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) (a6989586621681170124 :: NonEmpty a) Source # | |
data ZipSym1 (a6989586621681170124 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b)) Source #
Instances
| SingI1 (ZipSym1 :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ZipSym1 a6989586621681170124 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621681170124 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681170125 :: NonEmpty b) Source # | |
type family ZipSym2 (a6989586621681170124 :: NonEmpty a) (a6989586621681170125 :: 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) (a6989586621681170113 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681170113 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621681170113 | |
data ZipWithSym1 (a6989586621681170113 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)) Source #
Instances
| SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym1 x) | |
| 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 a6989586621681170113 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621681170113 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681170114 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym1 a6989586621681170113 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681170114 :: NonEmpty a) = ZipWithSym2 a6989586621681170113 a6989586621681170114 | |
data ZipWithSym2 (a6989586621681170113 :: (~>) a ((~>) b c)) (a6989586621681170114 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c) Source #
Instances
| SingI d => SingI1 (ZipWithSym2 d :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing :: forall (x :: k1). Sing x -> Sing (ZipWithSym2 d x) | |
| SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (ZipWithSym2 x y) | |
| (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 a6989586621681170113 a6989586621681170114 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621681170113 a6989586621681170114 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681170115 :: NonEmpty b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ZipWithSym3 (a6989586621681170113 :: (~>) a ((~>) b c)) (a6989586621681170114 :: NonEmpty a) (a6989586621681170115 :: NonEmpty b) :: NonEmpty c where ... Source #
Equations
| ZipWithSym3 a6989586621681170113 a6989586621681170114 a6989586621681170115 = ZipWith a6989586621681170113 a6989586621681170114 a6989586621681170115 |
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) (a6989586621681170087 :: NonEmpty (a, b)) Source # | |
type family UnzipSym1 (a6989586621681170087 :: 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) (a6989586621681170449 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681170449 :: [a]) = FromList a6989586621681170449 | |
type family FromListSym1 (a6989586621681170449 :: [a]) :: NonEmpty a where ... Source #
Equations
| FromListSym1 a6989586621681170449 = FromList a6989586621681170449 |
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) (a6989586621681170444 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681170444 :: NonEmpty a) = ToList a6989586621681170444 | |
type family ToListSym1 (a6989586621681170444 :: NonEmpty a) :: [a] where ... Source #
Equations
| ToListSym1 a6989586621681170444 = ToList a6989586621681170444 |
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 | |
| 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) (a6989586621681170527 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621681170527 :: [a]) = NonEmpty_ a6989586621681170527 | |
type family NonEmpty_Sym1 (a6989586621681170527 :: [a]) :: Maybe (NonEmpty a) where ... Source #
Equations
| NonEmpty_Sym1 a6989586621681170527 = NonEmpty_ a6989586621681170527 |
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 (a6989586621681170547 :: NonEmpty Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
Orphan instances
| PMonadZip NonEmpty Source # | |
| 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 # | |