| Copyright | (C) 2016 Richard Eisenberg |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Ryan Scott |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| Language | GHC2021 |
Data.List.NonEmpty.Singletons
Description
Defines functions and datatypes relating to the singleton for NonEmpty,
including singled versions of all the definitions in Data.List.NonEmpty.
Because many of these definitions are produced by Template Haskell,
it is not possible to create proper Haddock documentation. Please look
up the corresponding operation in Data.List.NonEmpty. Also, please excuse
the apparent repeated variable names. This is due to an interaction
between Template Haskell and Haddock.
Synopsis
- type family Sing :: k -> Type
- data SNonEmpty :: forall (a :: Type). NonEmpty a -> Type where
- type family Map (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty b where ...
- sMap :: forall (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) :: Type
- type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
- sIntersperse :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a) :: Type
- type family Scanl (a :: (~>) b ((~>) a b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
- sScanl :: forall (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
- type family Scanr (a :: (~>) a ((~>) b b)) (a :: b) (a :: [a]) :: NonEmpty b where ...
- sScanr :: forall (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
- type family Scanl1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
- sScanl1 :: forall (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) :: Type
- type family Scanr1 (a :: (~>) a ((~>) a a)) (a :: NonEmpty a) :: NonEmpty a where ...
- sScanr1 :: forall (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) :: Type
- type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- sTranspose :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a)) :: Type
- type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ...
- sSortBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a) :: Type
- type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ...
- sSortWith :: forall (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a) :: Type
- type family Length (a :: NonEmpty a) :: Natural where ...
- sLength :: forall (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Natural) :: Type
- type family Head (a :: NonEmpty a) :: a where ...
- sHead :: forall (t :: NonEmpty a). Sing t -> Sing (Apply HeadSym0 t :: a) :: Type
- type family Tail (a :: NonEmpty a) :: [a] where ...
- sTail :: forall (t :: NonEmpty a). Sing t -> Sing (Apply TailSym0 t :: [a]) :: Type
- type family Last (a :: NonEmpty a) :: a where ...
- sLast :: forall (t :: NonEmpty a). Sing t -> Sing (Apply LastSym0 t :: a) :: Type
- type family Init (a :: NonEmpty a) :: [a] where ...
- sInit :: forall (t :: NonEmpty a). Sing t -> Sing (Apply InitSym0 t :: [a]) :: Type
- type family (a :: a) <| (a :: NonEmpty a) :: NonEmpty a where ...
- (%<|) :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a) :: Type
- type family Cons (a :: a) (a :: NonEmpty a) :: NonEmpty a where ...
- sCons :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a) :: Type
- type family Uncons (a :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- sUncons :: forall (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) :: Type
- type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
- sUnfoldr :: forall (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) :: Type
- type family Sort (a :: NonEmpty a) :: NonEmpty a where ...
- sSort :: forall (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) :: Type
- type family Reverse (a :: NonEmpty a) :: NonEmpty a where ...
- sReverse :: forall (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a) :: Type
- type family Inits (a :: [a]) :: NonEmpty [a] where ...
- sInits :: forall (t :: [a]). Sing t -> Sing (Apply InitsSym0 t :: NonEmpty [a]) :: Type
- type family Tails (a :: [a]) :: NonEmpty [a] where ...
- sTails :: forall (t :: [a]). Sing t -> Sing (Apply TailsSym0 t :: NonEmpty [a]) :: Type
- type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ...
- sUnfold :: forall (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) :: Type
- type family Insert (a :: a) (a :: [a]) :: NonEmpty a where ...
- sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) :: Type
- type family Take (a :: Natural) (a :: NonEmpty a) :: [a] where ...
- sTake :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) :: Type
- type family Drop (a :: Natural) (a :: NonEmpty a) :: [a] where ...
- sDrop :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) :: Type
- type family SplitAt (a :: Natural) (a :: NonEmpty a) :: ([a], [a]) where ...
- sSplitAt :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) :: Type
- type family TakeWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sTakeWhile :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) :: Type
- type family DropWhile (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sDropWhile :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) :: Type
- type family Span (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sSpan :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) :: Type
- type family Break (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sBreak :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) :: Type
- type family Filter (a :: (~>) a Bool) (a :: NonEmpty a) :: [a] where ...
- sFilter :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) :: Type
- type family Partition (a :: (~>) a Bool) (a :: NonEmpty a) :: ([a], [a]) where ...
- sPartition :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) :: Type
- type family Group (a :: [a]) :: [NonEmpty a] where ...
- sGroup :: forall (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [NonEmpty a]) :: Type
- type family GroupBy (a :: (~>) a ((~>) a Bool)) (a :: [a]) :: [NonEmpty a] where ...
- sGroupBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a]) :: Type
- type family GroupWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
- sGroupWith :: forall (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a]) :: Type
- type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ...
- sGroupAllWith :: forall (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a]) :: Type
- type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroup1 :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) :: Type
- type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupBy1 :: forall (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type
- type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupWith1 :: forall (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type
- type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- sGroupAllWith1 :: forall (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type
- type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ...
- sIsPrefixOf :: forall (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) :: Type
- type family Nub (a :: NonEmpty a) :: NonEmpty a where ...
- sNub :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a) :: Type
- type family NubBy (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty a where ...
- sNubBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a) :: Type
- type family (a :: NonEmpty a) !! (a :: Natural) :: a where ...
- (%!!) :: forall (t :: NonEmpty a) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) :: Type
- type family Zip (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty (a, b) where ...
- sZip :: forall (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) :: Type
- type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ...
- sZipWith :: forall (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
- type family Unzip (a :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- sUnzip :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) :: Type
- type family FromList (a :: [a]) :: NonEmpty a where ...
- sFromList :: forall (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a) :: Type
- type family ToList (a :: NonEmpty a) :: [a] where ...
- sToList :: forall (t :: NonEmpty a). Sing t -> Sing (Apply ToListSym0 t :: [a]) :: Type
- type family NonEmpty_ (a :: [a]) :: Maybe (NonEmpty a) where ...
- sNonEmpty_ :: forall (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) :: Type
- type family Xor (a :: NonEmpty Bool) :: Bool where ...
- sXor :: forall (t :: NonEmpty Bool). Sing t -> Sing (Apply XorSym0 t :: Bool) :: Type
- data (:|@#@$) :: (~>) a ((~>) [a] (NonEmpty (a :: Type)))
- data (:|@#@$$) (a6989586621679037625 :: a) :: (~>) [a] (NonEmpty (a :: Type))
- type family (a6989586621679037625 :: a) :|@#@$$$ (a6989586621679037626 :: [a]) :: NonEmpty (a :: Type) where ...
- data MapSym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty b))
- data MapSym1 (a6989586621680610103 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b)
- type family MapSym2 (a6989586621680610103 :: (~>) a b) (a6989586621680610104 :: NonEmpty a) :: NonEmpty b where ...
- data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data IntersperseSym1 (a6989586621680610031 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family IntersperseSym2 (a6989586621680610031 :: a) (a6989586621680610032 :: NonEmpty a) :: NonEmpty a where ...
- data ScanlSym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanlSym1 (a6989586621680610073 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanlSym2 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanlSym3 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) (a6989586621680610075 :: [a]) :: NonEmpty b where ...
- data ScanrSym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) [a] (NonEmpty b)))
- data ScanrSym1 (a6989586621680610061 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b))
- data ScanrSym2 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) :: (~>) [a] (NonEmpty b)
- type family ScanrSym3 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) (a6989586621680610063 :: [a]) :: NonEmpty b where ...
- data Scanl1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanl1Sym1 (a6989586621680610050 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanl1Sym2 (a6989586621680610050 :: (~>) a ((~>) a a)) (a6989586621680610051 :: NonEmpty a) :: NonEmpty a where ...
- data Scanr1Sym0 :: (~>) ((~>) a ((~>) a a)) ((~>) (NonEmpty a) (NonEmpty a))
- data Scanr1Sym1 (a6989586621680610042 :: (~>) a ((~>) a a)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family Scanr1Sym2 (a6989586621680610042 :: (~>) a ((~>) a a)) (a6989586621680610043 :: NonEmpty a) :: NonEmpty a where ...
- data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a))
- type family TransposeSym1 (a6989586621680609740 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ...
- data SortBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (NonEmpty a) (NonEmpty a))
- data SortBySym1 (a6989586621680609732 :: (~>) a ((~>) a Ordering)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortBySym2 (a6989586621680609732 :: (~>) a ((~>) a Ordering)) (a6989586621680609733 :: NonEmpty a) :: NonEmpty a where ...
- data SortWithSym0 :: (~>) ((~>) a o) ((~>) (NonEmpty a) (NonEmpty a))
- data SortWithSym1 (a6989586621680609723 :: (~>) a o) :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortWithSym2 (a6989586621680609723 :: (~>) a o) (a6989586621680609724 :: NonEmpty a) :: NonEmpty a where ...
- data LengthSym0 :: (~>) (NonEmpty a) Natural
- type family LengthSym1 (a6989586621680610233 :: NonEmpty a) :: Natural where ...
- data HeadSym0 :: (~>) (NonEmpty a) a
- type family HeadSym1 (a6989586621680610168 :: NonEmpty a) :: a where ...
- data TailSym0 :: (~>) (NonEmpty a) [a]
- type family TailSym1 (a6989586621680610164 :: NonEmpty a) :: [a] where ...
- data LastSym0 :: (~>) (NonEmpty a) a
- type family LastSym1 (a6989586621680610159 :: NonEmpty a) :: a where ...
- data InitSym0 :: (~>) (NonEmpty a) [a]
- type family InitSym1 (a6989586621680610154 :: NonEmpty a) :: [a] where ...
- data (<|@#@$) :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data (<|@#@$$) (a6989586621680610147 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family (a6989586621680610147 :: a) <|@#@$$$ (a6989586621680610148 :: NonEmpty a) :: NonEmpty a where ...
- data ConsSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a))
- data ConsSym1 (a6989586621680610140 :: a) :: (~>) (NonEmpty a) (NonEmpty a)
- type family ConsSym2 (a6989586621680610140 :: a) (a6989586621680610141 :: NonEmpty a) :: NonEmpty a where ...
- data UnconsSym0 :: (~>) (NonEmpty a) (a, Maybe (NonEmpty a))
- type family UnconsSym1 (a6989586621680610197 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ...
- data UnfoldrSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldrSym1 (a6989586621680610173 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- type family UnfoldrSym2 (a6989586621680610173 :: (~>) a (b, Maybe a)) (a6989586621680610174 :: a) :: NonEmpty b where ...
- data SortSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family SortSym1 (a6989586621680610131 :: NonEmpty a) :: NonEmpty a where ...
- data ReverseSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family ReverseSym1 (a6989586621680610026 :: NonEmpty a) :: NonEmpty a where ...
- data InitsSym0 :: (~>) [a] (NonEmpty [a])
- type family InitsSym1 (a6989586621680610098 :: [a]) :: NonEmpty [a] where ...
- data TailsSym0 :: (~>) [a] (NonEmpty [a])
- type family TailsSym1 (a6989586621680610092 :: [a]) :: NonEmpty [a] where ...
- data UnfoldSym0 :: (~>) ((~>) a (b, Maybe a)) ((~>) a (NonEmpty b))
- data UnfoldSym1 (a6989586621680610208 :: (~>) a (b, Maybe a)) :: (~>) a (NonEmpty b)
- data InsertSym0 :: (~>) a ((~>) [a] (NonEmpty a))
- data InsertSym1 (a6989586621680610084 :: a) :: (~>) [a] (NonEmpty a)
- type family InsertSym2 (a6989586621680610084 :: a) (a6989586621680610085 :: [a]) :: NonEmpty a where ...
- data TakeSym0 :: (~>) Natural ((~>) (NonEmpty a) [a])
- data TakeSym1 (a6989586621680610018 :: Natural) :: (~>) (NonEmpty a) [a]
- type family TakeSym2 (a6989586621680610018 :: Natural) (a6989586621680610019 :: NonEmpty a) :: [a] where ...
- data DropSym0 :: (~>) Natural ((~>) (NonEmpty a) [a])
- data DropSym1 (a6989586621680610009 :: Natural) :: (~>) (NonEmpty a) [a]
- type family DropSym2 (a6989586621680610009 :: Natural) (a6989586621680610010 :: NonEmpty a) :: [a] where ...
- data SplitAtSym0 :: (~>) Natural ((~>) (NonEmpty a) ([a], [a]))
- data SplitAtSym1 (a6989586621680610000 :: Natural) :: (~>) (NonEmpty a) ([a], [a])
- type family SplitAtSym2 (a6989586621680610000 :: Natural) (a6989586621680610001 :: NonEmpty a) :: ([a], [a]) where ...
- data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data TakeWhileSym1 (a6989586621680609991 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family TakeWhileSym2 (a6989586621680609991 :: (~>) a Bool) (a6989586621680609992 :: NonEmpty a) :: [a] where ...
- data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data DropWhileSym1 (a6989586621680609982 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family DropWhileSym2 (a6989586621680609982 :: (~>) a Bool) (a6989586621680609983 :: NonEmpty a) :: [a] where ...
- data SpanSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data SpanSym1 (a6989586621680609973 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family SpanSym2 (a6989586621680609973 :: (~>) a Bool) (a6989586621680609974 :: NonEmpty a) :: ([a], [a]) where ...
- data BreakSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data BreakSym1 (a6989586621680609964 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family BreakSym2 (a6989586621680609964 :: (~>) a Bool) (a6989586621680609965 :: NonEmpty a) :: ([a], [a]) where ...
- data FilterSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a])
- data FilterSym1 (a6989586621680609955 :: (~>) a Bool) :: (~>) (NonEmpty a) [a]
- type family FilterSym2 (a6989586621680609955 :: (~>) a Bool) (a6989586621680609956 :: NonEmpty a) :: [a] where ...
- data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a]))
- data PartitionSym1 (a6989586621680609946 :: (~>) a Bool) :: (~>) (NonEmpty a) ([a], [a])
- type family PartitionSym2 (a6989586621680609946 :: (~>) a Bool) (a6989586621680609947 :: NonEmpty a) :: ([a], [a]) where ...
- data GroupSym0 :: (~>) [a] [NonEmpty a]
- type family GroupSym1 (a6989586621680609939 :: [a]) :: [NonEmpty a] where ...
- data GroupBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) [a] [NonEmpty a])
- data GroupBySym1 (a6989586621680609906 :: (~>) a ((~>) a Bool)) :: (~>) [a] [NonEmpty a]
- type family GroupBySym2 (a6989586621680609906 :: (~>) a ((~>) a Bool)) (a6989586621680609907 :: [a]) :: [NonEmpty a] where ...
- data GroupWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupWithSym1 (a6989586621680609897 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupWithSym2 (a6989586621680609897 :: (~>) a b) (a6989586621680609898 :: [a]) :: [NonEmpty a] where ...
- data GroupAllWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a])
- data GroupAllWithSym1 (a6989586621680609888 :: (~>) a b) :: (~>) [a] [NonEmpty a]
- type family GroupAllWithSym2 (a6989586621680609888 :: (~>) a b) (a6989586621680609889 :: [a]) :: [NonEmpty a] where ...
- data Group1Sym0 :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family Group1Sym1 (a6989586621680609881 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupBy1Sym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupBy1Sym1 (a6989586621680609854 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupBy1Sym2 (a6989586621680609854 :: (~>) a ((~>) a Bool)) (a6989586621680609855 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupWith1Sym1 (a6989586621680609847 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupWith1Sym2 (a6989586621680609847 :: (~>) a b) (a6989586621680609848 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data GroupAllWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a)))
- data GroupAllWith1Sym1 (a6989586621680609838 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty (NonEmpty a))
- type family GroupAllWith1Sym2 (a6989586621680609838 :: (~>) a b) (a6989586621680609839 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ...
- data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool)
- data IsPrefixOfSym1 (a6989586621680609827 :: [a]) :: (~>) (NonEmpty a) Bool
- type family IsPrefixOfSym2 (a6989586621680609827 :: [a]) (a6989586621680609828 :: NonEmpty a) :: Bool where ...
- data NubSym0 :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubSym1 (a6989586621680609758 :: NonEmpty a) :: NonEmpty a where ...
- data NubBySym0 :: (~>) ((~>) a ((~>) a Bool)) ((~>) (NonEmpty a) (NonEmpty a))
- data NubBySym1 (a6989586621680609745 :: (~>) a ((~>) a Bool)) :: (~>) (NonEmpty a) (NonEmpty a)
- type family NubBySym2 (a6989586621680609745 :: (~>) a ((~>) a Bool)) (a6989586621680609746 :: NonEmpty a) :: NonEmpty a where ...
- data (!!@#@$) :: (~>) (NonEmpty a) ((~>) Natural a)
- data (!!@#@$$) (a6989586621680609808 :: NonEmpty a) :: (~>) Natural a
- type family (a6989586621680609808 :: NonEmpty a) !!@#@$$$ (a6989586621680609809 :: Natural) :: a where ...
- data ZipSym0 :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty (a, b)))
- data ZipSym1 (a6989586621680609799 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b))
- type family ZipSym2 (a6989586621680609799 :: NonEmpty a) (a6989586621680609800 :: NonEmpty b) :: NonEmpty (a, b) where ...
- data ZipWithSym0 :: (~>) ((~>) a ((~>) b c)) ((~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c)))
- data ZipWithSym1 (a6989586621680609788 :: (~>) a ((~>) b c)) :: (~>) (NonEmpty a) ((~>) (NonEmpty b) (NonEmpty c))
- data ZipWithSym2 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty c)
- type family ZipWithSym3 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: NonEmpty a) (a6989586621680609790 :: NonEmpty b) :: NonEmpty c where ...
- data UnzipSym0 :: (~>) (NonEmpty (a, b)) (NonEmpty a, NonEmpty b)
- type family UnzipSym1 (a6989586621680609762 :: NonEmpty (a, b)) :: (NonEmpty a, NonEmpty b) where ...
- data FromListSym0 :: (~>) [a] (NonEmpty a)
- type family FromListSym1 (a6989586621680610124 :: [a]) :: NonEmpty a where ...
- data ToListSym0 :: (~>) (NonEmpty a) [a]
- type family ToListSym1 (a6989586621680610119 :: NonEmpty a) :: [a] where ...
- data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a))
- type family NonEmpty_Sym1 (a6989586621680610202 :: [a]) :: Maybe (NonEmpty a) where ...
- data XorSym0 :: (~>) (NonEmpty Bool) Bool
- type family XorSym1 (a6989586621680610222 :: NonEmpty Bool) :: Bool where ...
The NonEmpty singleton
type family Sing :: k -> Type #
The singleton kind-indexed type family.
Instances
data SNonEmpty :: forall (a :: Type). NonEmpty a -> Type where Source #
Constructors
| (:%|) :: forall (a :: Type) (n :: a) (n :: [a]). (Sing n) -> (Sing n) -> SNonEmpty ('(:|) n n :: NonEmpty (a :: Type)) infixr 5 |
Instances
| (SDecide a, SDecide [a]) => TestCoercion (SNonEmpty :: NonEmpty a -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods testCoercion :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (Coercion a0 b) | |
| (SDecide a, SDecide [a]) => TestEquality (SNonEmpty :: NonEmpty a -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods testEquality :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (a0 :~: b) | |
| (ShowSing a, ShowSing [a]) => Show (SNonEmpty z) Source # | |
Non-empty stream transformations
sMap :: forall (t :: (~>) a b) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply MapSym0 t) t :: NonEmpty b) :: Type Source #
type family Intersperse (a :: a) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Intersperse a ('(:|) b bs) = Apply (Apply (:|@#@$) b) (Case_6989586621680610036 a b bs bs) |
sIntersperse :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply IntersperseSym0 t) t :: NonEmpty a) :: Type Source #
sScanl :: forall (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 Source #
sScanr :: forall (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 Source #
sScanl1 :: forall (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanl1Sym0 t) t :: NonEmpty a) :: Type Source #
sScanr1 :: forall (t :: (~>) a ((~>) a a)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply Scanr1Sym0 t) t :: NonEmpty a) :: Type Source #
type family Transpose (a :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Transpose a_6989586621680609736 = Apply (Apply (Apply (.@#@$) (Apply FmapSym0 FromListSym0)) (Apply (Apply (.@#@$) FromListSym0) (Apply (Apply (.@#@$) ListtransposeSym0) (Apply (Apply (.@#@$) ToListSym0) (Apply FmapSym0 ToListSym0))))) a_6989586621680609736 |
sTranspose :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply TransposeSym0 t :: NonEmpty (NonEmpty a)) :: Type Source #
type family SortBy (a :: (~>) a ((~>) a Ordering)) (a :: NonEmpty a) :: NonEmpty a where ... Source #
sSortBy :: forall (t :: (~>) a ((~>) a Ordering)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SortBySym0 t) t :: NonEmpty a) :: Type Source #
type family SortWith (a :: (~>) a o) (a :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortWith a_6989586621680609716 a_6989586621680609718 = Apply (Apply (Apply (Apply (.@#@$) SortBySym0) ComparingSym0) a_6989586621680609716) a_6989586621680609718 |
sSortWith :: forall (t :: (~>) a o) (t :: NonEmpty a). SOrd o => Sing t -> Sing t -> Sing (Apply (Apply SortWithSym0 t) t :: NonEmpty a) :: Type Source #
sLength :: forall (t :: NonEmpty a). Sing t -> Sing (Apply LengthSym0 t :: Natural) :: Type Source #
(%<|) :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply (<|@#@$) t) t :: NonEmpty a) :: Type Source #
sCons :: forall (t :: a) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply ConsSym0 t) t :: NonEmpty a) :: Type 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 (t :: NonEmpty a). Sing t -> Sing (Apply UnconsSym0 t :: (a, Maybe (NonEmpty a))) :: Type Source #
type family Unfoldr (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #
Equations
| Unfoldr f a = Case_6989586621680610190 f a (Let6989586621680610188Scrutinee_6989586621680608752Sym2 f a) |
sUnfoldr :: forall (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldrSym0 t) t :: NonEmpty b) :: Type Source #
sSort :: forall (t :: NonEmpty a). SOrd a => Sing t -> Sing (Apply SortSym0 t :: NonEmpty a) :: Type Source #
sReverse :: forall (t :: NonEmpty a). Sing t -> Sing (Apply ReverseSym0 t :: NonEmpty a) :: Type Source #
type family Unfold (a :: (~>) a (b, Maybe a)) (a :: a) :: NonEmpty b where ... Source #
Equations
| Unfold f a = Case_6989586621680610214 f a (Let6989586621680610212Scrutinee_6989586621680608742Sym2 f a) |
sUnfold :: forall (t :: (~>) a (b, Maybe a)) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply UnfoldSym0 t) t :: NonEmpty b) :: Type Source #
sInsert :: forall (t :: a) (t :: [a]). SOrd a => Sing t -> Sing t -> Sing (Apply (Apply InsertSym0 t) t :: NonEmpty a) :: Type Source #
sTake :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeSym0 t) t :: [a]) :: Type Source #
sDrop :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropSym0 t) t :: [a]) :: Type Source #
sSplitAt :: forall (t :: Natural) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SplitAtSym0 t) t :: ([a], [a])) :: Type Source #
sTakeWhile :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply TakeWhileSym0 t) t :: [a]) :: Type Source #
sDropWhile :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply DropWhileSym0 t) t :: [a]) :: Type Source #
sSpan :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply SpanSym0 t) t :: ([a], [a])) :: Type Source #
sBreak :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply BreakSym0 t) t :: ([a], [a])) :: Type Source #
sFilter :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply FilterSym0 t) t :: [a]) :: Type Source #
sPartition :: forall (t :: (~>) a Bool) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply PartitionSym0 t) t :: ([a], [a])) :: Type Source #
type family Group (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| Group a_6989586621680609935 = Apply (Apply GroupBySym0 (==@#@$)) a_6989586621680609935 |
sGroup :: forall (t :: [a]). SEq a => Sing t -> Sing (Apply GroupSym0 t :: [NonEmpty a]) :: Type Source #
sGroupBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply GroupBySym0 t) t :: [NonEmpty a]) :: Type Source #
sGroupWith :: forall (t :: (~>) a b) (t :: [a]). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWithSym0 t) t :: [NonEmpty a]) :: Type Source #
type family GroupAllWith (a :: (~>) a b) (a :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupAllWith f a_6989586621680609883 = Apply (Apply (Apply (.@#@$) (Apply GroupWithSym0 f)) (Apply ListsortBySym0 (Apply (Apply OnSym0 CompareSym0) f))) a_6989586621680609883 |
sGroupAllWith :: forall (t :: (~>) a b) (t :: [a]). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWithSym0 t) t :: [NonEmpty a]) :: Type Source #
type family Group1 (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Group1 a_6989586621680609877 = Apply (Apply GroupBy1Sym0 (==@#@$)) a_6989586621680609877 |
sGroup1 :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply Group1Sym0 t :: NonEmpty (NonEmpty a)) :: Type Source #
type family GroupBy1 (a :: (~>) a ((~>) a Bool)) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
sGroupBy1 :: forall (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply GroupBy1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type Source #
type family GroupWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupWith1 f a_6989586621680609842 = Apply (Apply GroupBy1Sym0 (Apply (Apply OnSym0 (==@#@$)) f)) a_6989586621680609842 |
sGroupWith1 :: forall (t :: (~>) a b) (t :: NonEmpty a). SEq b => Sing t -> Sing t -> Sing (Apply (Apply GroupWith1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type Source #
type family GroupAllWith1 (a :: (~>) a b) (a :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupAllWith1 f a_6989586621680609833 = Apply (Apply (Apply (.@#@$) (Apply GroupWith1Sym0 f)) (Apply SortWithSym0 f)) a_6989586621680609833 |
sGroupAllWith1 :: forall (t :: (~>) a b) (t :: NonEmpty a). SOrd b => Sing t -> Sing t -> Sing (Apply (Apply GroupAllWith1Sym0 t) t :: NonEmpty (NonEmpty a)) :: Type Source #
type family IsPrefixOf (a :: [a]) (a :: NonEmpty a) :: Bool where ... Source #
sIsPrefixOf :: forall (t :: [a]) (t :: NonEmpty a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply IsPrefixOfSym0 t) t :: Bool) :: Type Source #
sNub :: forall (t :: NonEmpty a). SEq a => Sing t -> Sing (Apply NubSym0 t :: NonEmpty a) :: Type Source #
sNubBy :: forall (t :: (~>) a ((~>) a Bool)) (t :: NonEmpty a). Sing t -> Sing t -> Sing (Apply (Apply NubBySym0 t) t :: NonEmpty a) :: Type Source #
type family (a :: NonEmpty a) !! (a :: Natural) :: a where ... Source #
Equations
| arg_6989586621680608764 !! arg_6989586621680608766 = Case_6989586621680609812 arg_6989586621680608764 arg_6989586621680608766 (Apply (Apply Tuple2Sym0 arg_6989586621680608764) arg_6989586621680608766) |
(%!!) :: forall (t :: NonEmpty a) (t :: Natural). Sing t -> Sing t -> Sing (Apply (Apply (!!@#@$) t) t :: a) :: Type Source #
sZip :: forall (t :: NonEmpty a) (t :: NonEmpty b). Sing t -> Sing t -> Sing (Apply (Apply ZipSym0 t) t :: NonEmpty (a, b)) :: Type Source #
type family ZipWith (a :: (~>) a ((~>) b c)) (a :: NonEmpty a) (a :: NonEmpty b) :: NonEmpty c where ... Source #
sZipWith :: forall (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 Source #
sUnzip :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply UnzipSym0 t :: (NonEmpty a, NonEmpty b)) :: Type Source #
sFromList :: forall (t :: [a]). Sing t -> Sing (Apply FromListSym0 t :: NonEmpty a) :: Type Source #
sNonEmpty_ :: forall (t :: [a]). Sing t -> Sing (Apply NonEmpty_Sym0 t :: Maybe (NonEmpty a)) :: Type 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) (a6989586621679037625 :: a) Source # | |
data (:|@#@$$) (a6989586621679037625 :: a) :: (~>) [a] (NonEmpty (a :: Type)) infixr 5 Source #
Instances
| SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) Source # | |
| SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances | |
| SuppressUnusedWarnings ((:|@#@$$) a6989586621679037625 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.Singletons.Base.Instances Methods suppressUnusedWarnings :: () # | |
| type Apply ((:|@#@$$) a6989586621679037625 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679037626 :: [a]) Source # | |
Defined in Data.Singletons.Base.Instances | |
type family (a6989586621679037625 :: a) :|@#@$$$ (a6989586621679037626 :: [a]) :: NonEmpty (a :: Type) where ... infixr 5 Source #
Equations
| a6989586621679037625 :|@#@$$$ a6989586621679037626 = '(:|) a6989586621679037625 a6989586621679037626 |
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) (a6989586621680610103 :: a ~> b) Source # | |
data MapSym1 (a6989586621680610103 :: (~>) a b) :: (~>) (NonEmpty a) (NonEmpty b) Source #
Instances
| SingI1 (MapSym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
| SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (MapSym1 a6989586621680610103 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (MapSym1 a6989586621680610103 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621680610104 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family MapSym2 (a6989586621680610103 :: (~>) a b) (a6989586621680610104 :: NonEmpty a) :: NonEmpty b where ... Source #
data IntersperseSym0 :: (~>) a ((~>) (NonEmpty a) (NonEmpty a)) Source #
Instances
| SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing IntersperseSym0 # | |
| SuppressUnusedWarnings (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680610031 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680610031 :: a) = IntersperseSym1 a6989586621680610031 | |
data IntersperseSym1 (a6989586621680610031 :: 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 a6989586621680610031 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IntersperseSym1 a6989586621680610031 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610032 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IntersperseSym1 a6989586621680610031 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610032 :: NonEmpty a) = Intersperse a6989586621680610031 a6989586621680610032 | |
type family IntersperseSym2 (a6989586621680610031 :: a) (a6989586621680610032 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| IntersperseSym2 a6989586621680610031 a6989586621680610032 = Intersperse a6989586621680610031 a6989586621680610032 |
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) (a6989586621680610073 :: b ~> (a ~> b)) Source # | |
data ScanlSym1 (a6989586621680610073 :: (~>) b ((~>) a b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
| SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym1 a6989586621680610073 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym1 a6989586621680610073 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680610074 :: b) Source # | |
data ScanlSym2 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanlSym2 a6989586621680610073 a6989586621680610074 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanlSym2 a6989586621680610073 a6989586621680610074 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610075 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ScanlSym3 (a6989586621680610073 :: (~>) b ((~>) a b)) (a6989586621680610074 :: b) (a6989586621680610075 :: [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) (a6989586621680610061 :: a ~> (b ~> b)) Source # | |
data ScanrSym1 (a6989586621680610061 :: (~>) a ((~>) b b)) :: (~>) b ((~>) [a] (NonEmpty b)) Source #
Instances
| SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
| SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym1 a6989586621680610061 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym1 a6989586621680610061 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680610062 :: b) Source # | |
data ScanrSym2 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) :: (~>) [a] (NonEmpty b) Source #
Instances
| SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # | |
| (SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ScanrSym2 a6989586621680610061 a6989586621680610062 :: TyFun [a] (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ScanrSym2 a6989586621680610061 a6989586621680610062 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680610063 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ScanrSym3 (a6989586621680610061 :: (~>) a ((~>) b b)) (a6989586621680610062 :: b) (a6989586621680610063 :: [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) (a6989586621680610050 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680610050 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621680610050 | |
data Scanl1Sym1 (a6989586621680610050 :: (~>) 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 a6989586621680610050 :: 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 a6989586621680610050 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610051 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanl1Sym1 a6989586621680610050 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610051 :: NonEmpty a) = Scanl1 a6989586621680610050 a6989586621680610051 | |
type family Scanl1Sym2 (a6989586621680610050 :: (~>) a ((~>) a a)) (a6989586621680610051 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanl1Sym2 a6989586621680610050 a6989586621680610051 = Scanl1 a6989586621680610050 a6989586621680610051 |
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) (a6989586621680610042 :: a ~> (a ~> a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680610042 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621680610042 | |
data Scanr1Sym1 (a6989586621680610042 :: (~>) 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 a6989586621680610042 :: 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 a6989586621680610042 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610043 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Scanr1Sym1 a6989586621680610042 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610043 :: NonEmpty a) = Scanr1 a6989586621680610042 a6989586621680610043 | |
type family Scanr1Sym2 (a6989586621680610042 :: (~>) a ((~>) a a)) (a6989586621680610043 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| Scanr1Sym2 a6989586621680610042 a6989586621680610043 = Scanr1 a6989586621680610042 a6989586621680610043 |
data TransposeSym0 :: (~>) (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) Source #
Instances
| SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing TransposeSym0 # | |
| SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609740 :: NonEmpty (NonEmpty a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609740 :: NonEmpty (NonEmpty a)) = Transpose a6989586621680609740 | |
type family TransposeSym1 (a6989586621680609740 :: NonEmpty (NonEmpty a)) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| TransposeSym1 a6989586621680609740 = Transpose a6989586621680609740 |
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) (a6989586621680609732 :: a ~> (a ~> Ordering)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680609732 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621680609732 | |
data SortBySym1 (a6989586621680609732 :: (~>) 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 a6989586621680609732 :: 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 a6989586621680609732 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609733 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortBySym1 a6989586621680609732 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609733 :: NonEmpty a) = SortBy a6989586621680609732 a6989586621680609733 | |
type family SortBySym2 (a6989586621680609732 :: (~>) a ((~>) a Ordering)) (a6989586621680609733 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortBySym2 a6989586621680609732 a6989586621680609733 = SortBy a6989586621680609732 a6989586621680609733 |
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) (a6989586621680609723 :: a ~> o) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680609723 :: a ~> o) = SortWithSym1 a6989586621680609723 | |
data SortWithSym1 (a6989586621680609723 :: (~>) 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 a6989586621680609723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SortWithSym1 a6989586621680609723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609724 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SortWithSym1 a6989586621680609723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609724 :: NonEmpty a) = SortWith a6989586621680609723 a6989586621680609724 | |
type family SortWithSym2 (a6989586621680609723 :: (~>) a o) (a6989586621680609724 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| SortWithSym2 a6989586621680609723 a6989586621680609724 = SortWith a6989586621680609723 a6989586621680609724 |
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) (a6989586621680610233 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621680610233 :: NonEmpty a) = Length a6989586621680610233 | |
type family LengthSym1 (a6989586621680610233 :: NonEmpty a) :: Natural where ... Source #
Equations
| LengthSym1 a6989586621680610233 = Length a6989586621680610233 |
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) (a6989586621680610168 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680610164 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680610159 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680610154 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680610147 :: a) Source # | |
data (<|@#@$$) (a6989586621680610147 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI1 ((<|@#@$$) :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
| SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((<|@#@$$) a6989586621680610147 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((<|@#@$$) a6989586621680610147 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610148 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family (a6989586621680610147 :: a) <|@#@$$$ (a6989586621680610148 :: 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) (a6989586621680610140 :: a) Source # | |
data ConsSym1 (a6989586621680610140 :: a) :: (~>) (NonEmpty a) (NonEmpty a) Source #
Instances
| SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
| SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ConsSym1 a6989586621680610140 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ConsSym1 a6989586621680610140 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610141 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ConsSym2 (a6989586621680610140 :: a) (a6989586621680610141 :: 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) (a6989586621680610197 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621680610197 :: NonEmpty a) = Uncons a6989586621680610197 | |
type family UnconsSym1 (a6989586621680610197 :: NonEmpty a) :: (a, Maybe (NonEmpty a)) where ... Source #
Equations
| UnconsSym1 a6989586621680610197 = Uncons a6989586621680610197 |
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) (a6989586621680610173 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680610173 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621680610173 | |
data UnfoldrSym1 (a6989586621680610173 :: (~>) 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 a6989586621680610173 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldrSym1 a6989586621680610173 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610174 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldrSym1 a6989586621680610173 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610174 :: a) = Unfoldr a6989586621680610173 a6989586621680610174 | |
type family UnfoldrSym2 (a6989586621680610173 :: (~>) a (b, Maybe a)) (a6989586621680610174 :: a) :: NonEmpty b where ... Source #
Equations
| UnfoldrSym2 a6989586621680610173 a6989586621680610174 = Unfoldr a6989586621680610173 a6989586621680610174 |
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) (a6989586621680610131 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680610026 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680610026 :: NonEmpty a) = Reverse a6989586621680610026 | |
type family ReverseSym1 (a6989586621680610026 :: NonEmpty a) :: NonEmpty a where ... Source #
Equations
| ReverseSym1 a6989586621680610026 = Reverse a6989586621680610026 |
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) (a6989586621680610098 :: [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) (a6989586621680610092 :: [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) (a6989586621680610208 :: a ~> (b, Maybe a)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680610208 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621680610208 | |
data UnfoldSym1 (a6989586621680610208 :: (~>) 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 a6989586621680610208 :: TyFun a (NonEmpty b) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (UnfoldSym1 a6989586621680610208 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610209 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (UnfoldSym1 a6989586621680610208 :: TyFun a (NonEmpty b) -> Type) (a6989586621680610209 :: a) = Unfold a6989586621680610208 a6989586621680610209 | |
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) (a6989586621680610084 :: a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680610084 :: a) = InsertSym1 a6989586621680610084 | |
data InsertSym1 (a6989586621680610084 :: 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 a6989586621680610084 :: TyFun [a] (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (InsertSym1 a6989586621680610084 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680610085 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (InsertSym1 a6989586621680610084 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680610085 :: [a]) = Insert a6989586621680610084 a6989586621680610085 | |
type family InsertSym2 (a6989586621680610084 :: a) (a6989586621680610085 :: [a]) :: NonEmpty a where ... Source #
Equations
| InsertSym2 a6989586621680610084 a6989586621680610085 = Insert a6989586621680610084 a6989586621680610085 |
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) (a6989586621680610018 :: Natural) Source # | |
data TakeSym1 (a6989586621680610018 :: Natural) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
| SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (TakeSym1 a6989586621680610018 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeSym1 a6989586621680610018 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680610019 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family TakeSym2 (a6989586621680610018 :: Natural) (a6989586621680610019 :: 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) (a6989586621680610009 :: Natural) Source # | |
data DropSym1 (a6989586621680610009 :: Natural) :: (~>) (NonEmpty a) [a] Source #
Instances
| SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # | |
| SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (DropSym1 a6989586621680610009 :: TyFun (NonEmpty a) [a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropSym1 a6989586621680610009 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680610010 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family DropSym2 (a6989586621680610009 :: Natural) (a6989586621680610010 :: 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) (a6989586621680610000 :: Natural) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680610000 :: Natural) = SplitAtSym1 a6989586621680610000 :: TyFun (NonEmpty a) ([a], [a]) -> Type | |
data SplitAtSym1 (a6989586621680610000 :: 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 a6989586621680610000 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (SplitAtSym1 a6989586621680610000 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680610001 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (SplitAtSym1 a6989586621680610000 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680610001 :: NonEmpty a) = SplitAt a6989586621680610000 a6989586621680610001 | |
type family SplitAtSym2 (a6989586621680610000 :: Natural) (a6989586621680610001 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| SplitAtSym2 a6989586621680610000 a6989586621680610001 = SplitAt a6989586621680610000 a6989586621680610001 |
data TakeWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing TakeWhileSym0 # | |
| SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680609991 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680609991 :: a ~> Bool) = TakeWhileSym1 a6989586621680609991 | |
data TakeWhileSym1 (a6989586621680609991 :: (~>) 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 a6989586621680609991 :: 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 a6989586621680609991 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609992 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (TakeWhileSym1 a6989586621680609991 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609992 :: NonEmpty a) = TakeWhile a6989586621680609991 a6989586621680609992 | |
type family TakeWhileSym2 (a6989586621680609991 :: (~>) a Bool) (a6989586621680609992 :: NonEmpty a) :: [a] where ... Source #
Equations
| TakeWhileSym2 a6989586621680609991 a6989586621680609992 = TakeWhile a6989586621680609991 a6989586621680609992 |
data DropWhileSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) [a]) Source #
Instances
| SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing DropWhileSym0 # | |
| SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680609982 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680609982 :: a ~> Bool) = DropWhileSym1 a6989586621680609982 | |
data DropWhileSym1 (a6989586621680609982 :: (~>) 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 a6989586621680609982 :: 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 a6989586621680609982 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609983 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (DropWhileSym1 a6989586621680609982 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609983 :: NonEmpty a) = DropWhile a6989586621680609982 a6989586621680609983 | |
type family DropWhileSym2 (a6989586621680609982 :: (~>) a Bool) (a6989586621680609983 :: NonEmpty a) :: [a] where ... Source #
Equations
| DropWhileSym2 a6989586621680609982 a6989586621680609983 = DropWhile a6989586621680609982 a6989586621680609983 |
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) (a6989586621680609973 :: a ~> Bool) Source # | |
data SpanSym1 (a6989586621680609973 :: (~>) 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 a6989586621680609973 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
| type Apply (SpanSym1 a6989586621680609973 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680609974 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family SpanSym2 (a6989586621680609973 :: (~>) a Bool) (a6989586621680609974 :: 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) (a6989586621680609964 :: a ~> Bool) Source # | |
data BreakSym1 (a6989586621680609964 :: (~>) 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 a6989586621680609964 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # | |
| type Apply (BreakSym1 a6989586621680609964 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680609965 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family BreakSym2 (a6989586621680609964 :: (~>) a Bool) (a6989586621680609965 :: 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) (a6989586621680609955 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680609955 :: a ~> Bool) = FilterSym1 a6989586621680609955 | |
data FilterSym1 (a6989586621680609955 :: (~>) 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 a6989586621680609955 :: 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 a6989586621680609955 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609956 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FilterSym1 a6989586621680609955 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680609956 :: NonEmpty a) = Filter a6989586621680609955 a6989586621680609956 | |
type family FilterSym2 (a6989586621680609955 :: (~>) a Bool) (a6989586621680609956 :: NonEmpty a) :: [a] where ... Source #
Equations
| FilterSym2 a6989586621680609955 a6989586621680609956 = Filter a6989586621680609955 a6989586621680609956 |
data PartitionSym0 :: (~>) ((~>) a Bool) ((~>) (NonEmpty a) ([a], [a])) Source #
Instances
| SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing PartitionSym0 # | |
| SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680609946 :: a ~> Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680609946 :: a ~> Bool) = PartitionSym1 a6989586621680609946 | |
data PartitionSym1 (a6989586621680609946 :: (~>) 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 a6989586621680609946 :: 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 a6989586621680609946 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680609947 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (PartitionSym1 a6989586621680609946 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680609947 :: NonEmpty a) = Partition a6989586621680609946 a6989586621680609947 | |
type family PartitionSym2 (a6989586621680609946 :: (~>) a Bool) (a6989586621680609947 :: NonEmpty a) :: ([a], [a]) where ... Source #
Equations
| PartitionSym2 a6989586621680609946 a6989586621680609947 = Partition a6989586621680609946 a6989586621680609947 |
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) (a6989586621680609939 :: [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) (a6989586621680609906 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680609906 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621680609906 | |
data GroupBySym1 (a6989586621680609906 :: (~>) 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 a6989586621680609906 :: 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 a6989586621680609906 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609907 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBySym1 a6989586621680609906 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609907 :: [a]) = GroupBy a6989586621680609906 a6989586621680609907 | |
type family GroupBySym2 (a6989586621680609906 :: (~>) a ((~>) a Bool)) (a6989586621680609907 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupBySym2 a6989586621680609906 a6989586621680609907 = GroupBy a6989586621680609906 a6989586621680609907 |
data GroupWithSym0 :: (~>) ((~>) a b) ((~>) [a] [NonEmpty a]) Source #
Instances
| SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing GroupWithSym0 # | |
| SuppressUnusedWarnings (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680609897 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680609897 :: a ~> b) = GroupWithSym1 a6989586621680609897 | |
data GroupWithSym1 (a6989586621680609897 :: (~>) 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 a6989586621680609897 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWithSym1 a6989586621680609897 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609898 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWithSym1 a6989586621680609897 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609898 :: [a]) = GroupWith a6989586621680609897 a6989586621680609898 | |
type family GroupWithSym2 (a6989586621680609897 :: (~>) a b) (a6989586621680609898 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupWithSym2 a6989586621680609897 a6989586621680609898 = GroupWith a6989586621680609897 a6989586621680609898 |
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) (a6989586621680609888 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680609888 :: a ~> b) = GroupAllWithSym1 a6989586621680609888 | |
data GroupAllWithSym1 (a6989586621680609888 :: (~>) 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 a6989586621680609888 :: TyFun [a] [NonEmpty a] -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWithSym1 a6989586621680609888 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609889 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWithSym1 a6989586621680609888 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680609889 :: [a]) = GroupAllWith a6989586621680609888 a6989586621680609889 | |
type family GroupAllWithSym2 (a6989586621680609888 :: (~>) a b) (a6989586621680609889 :: [a]) :: [NonEmpty a] where ... Source #
Equations
| GroupAllWithSym2 a6989586621680609888 a6989586621680609889 = GroupAllWith a6989586621680609888 a6989586621680609889 |
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) (a6989586621680609881 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609881 :: NonEmpty a) = Group1 a6989586621680609881 | |
type family Group1Sym1 (a6989586621680609881 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| Group1Sym1 a6989586621680609881 = Group1 a6989586621680609881 |
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) (a6989586621680609854 :: a ~> (a ~> Bool)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680609854 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621680609854 | |
data GroupBy1Sym1 (a6989586621680609854 :: (~>) 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 a6989586621680609854 :: 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 a6989586621680609854 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609855 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupBy1Sym1 a6989586621680609854 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609855 :: NonEmpty a) = GroupBy1 a6989586621680609854 a6989586621680609855 | |
type family GroupBy1Sym2 (a6989586621680609854 :: (~>) a ((~>) a Bool)) (a6989586621680609855 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupBy1Sym2 a6989586621680609854 a6989586621680609855 = GroupBy1 a6989586621680609854 a6989586621680609855 |
data GroupWith1Sym0 :: (~>) ((~>) a b) ((~>) (NonEmpty a) (NonEmpty (NonEmpty a))) Source #
Instances
| SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing GroupWith1Sym0 # | |
| SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680609847 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680609847 :: a ~> b) = GroupWith1Sym1 a6989586621680609847 | |
data GroupWith1Sym1 (a6989586621680609847 :: (~>) 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 a6989586621680609847 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupWith1Sym1 a6989586621680609847 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609848 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupWith1Sym1 a6989586621680609847 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609848 :: NonEmpty a) = GroupWith1 a6989586621680609847 a6989586621680609848 | |
type family GroupWith1Sym2 (a6989586621680609847 :: (~>) a b) (a6989586621680609848 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupWith1Sym2 a6989586621680609847 a6989586621680609848 = GroupWith1 a6989586621680609847 a6989586621680609848 |
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) (a6989586621680609838 :: a ~> b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680609838 :: a ~> b) = GroupAllWith1Sym1 a6989586621680609838 | |
data GroupAllWith1Sym1 (a6989586621680609838 :: (~>) 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 a6989586621680609838 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (GroupAllWith1Sym1 a6989586621680609838 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609839 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (GroupAllWith1Sym1 a6989586621680609838 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680609839 :: NonEmpty a) = GroupAllWith1 a6989586621680609838 a6989586621680609839 | |
type family GroupAllWith1Sym2 (a6989586621680609838 :: (~>) a b) (a6989586621680609839 :: NonEmpty a) :: NonEmpty (NonEmpty a) where ... Source #
Equations
| GroupAllWith1Sym2 a6989586621680609838 a6989586621680609839 = GroupAllWith1 a6989586621680609838 a6989586621680609839 |
data IsPrefixOfSym0 :: (~>) [a] ((~>) (NonEmpty a) Bool) Source #
Instances
| SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing IsPrefixOfSym0 # | |
| SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680609827 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680609827 :: [a]) = IsPrefixOfSym1 a6989586621680609827 | |
data IsPrefixOfSym1 (a6989586621680609827 :: [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 a6989586621680609827 :: TyFun (NonEmpty a) Bool -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (IsPrefixOfSym1 a6989586621680609827 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680609828 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (IsPrefixOfSym1 a6989586621680609827 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680609828 :: NonEmpty a) = IsPrefixOf a6989586621680609827 a6989586621680609828 | |
type family IsPrefixOfSym2 (a6989586621680609827 :: [a]) (a6989586621680609828 :: NonEmpty a) :: Bool where ... Source #
Equations
| IsPrefixOfSym2 a6989586621680609827 a6989586621680609828 = IsPrefixOf a6989586621680609827 a6989586621680609828 |
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) (a6989586621680609758 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
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) (a6989586621680609745 :: a ~> (a ~> Bool)) Source # | |
data NubBySym1 (a6989586621680609745 :: (~>) 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 a6989586621680609745 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # | |
| type Apply (NubBySym1 a6989586621680609745 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680609746 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family NubBySym2 (a6989586621680609745 :: (~>) a ((~>) a Bool)) (a6989586621680609746 :: 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) (a6989586621680609808 :: NonEmpty a) Source # | |
data (!!@#@$$) (a6989586621680609808 :: NonEmpty a) :: (~>) Natural a Source #
Instances
| SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # | |
| SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings ((!!@#@$$) a6989586621680609808 :: TyFun Natural a -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply ((!!@#@$$) a6989586621680609808 :: TyFun Natural a -> Type) (a6989586621680609809 :: Natural) Source # | |
type family (a6989586621680609808 :: NonEmpty a) !!@#@$$$ (a6989586621680609809 :: 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) (a6989586621680609799 :: NonEmpty a) Source # | |
data ZipSym1 (a6989586621680609799 :: NonEmpty a) :: (~>) (NonEmpty b) (NonEmpty (a, b)) Source #
Instances
| SingI1 (ZipSym1 :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
| SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
| SuppressUnusedWarnings (ZipSym1 a6989586621680609799 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipSym1 a6989586621680609799 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621680609800 :: NonEmpty b) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family ZipSym2 (a6989586621680609799 :: NonEmpty a) (a6989586621680609800 :: 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) (a6989586621680609788 :: a ~> (b ~> c)) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680609788 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621680609788 | |
data ZipWithSym1 (a6989586621680609788 :: (~>) 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 a6989586621680609788 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym1 a6989586621680609788 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680609789 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym1 a6989586621680609788 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680609789 :: NonEmpty a) = ZipWithSym2 a6989586621680609788 a6989586621680609789 | |
data ZipWithSym2 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: 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 | |
| (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 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (ZipWithSym2 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680609790 :: NonEmpty b) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ZipWithSym2 a6989586621680609788 a6989586621680609789 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680609790 :: NonEmpty b) = ZipWith a6989586621680609788 a6989586621680609789 a6989586621680609790 | |
type family ZipWithSym3 (a6989586621680609788 :: (~>) a ((~>) b c)) (a6989586621680609789 :: NonEmpty a) (a6989586621680609790 :: NonEmpty b) :: NonEmpty c where ... Source #
Equations
| ZipWithSym3 a6989586621680609788 a6989586621680609789 a6989586621680609790 = ZipWith a6989586621680609788 a6989586621680609789 a6989586621680609790 |
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) (a6989586621680609762 :: NonEmpty (a, b)) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
type family UnzipSym1 (a6989586621680609762 :: 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) (a6989586621680610124 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680610124 :: [a]) = FromList a6989586621680610124 | |
type family FromListSym1 (a6989586621680610124 :: [a]) :: NonEmpty a where ... Source #
Equations
| FromListSym1 a6989586621680610124 = FromList a6989586621680610124 |
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) (a6989586621680610119 :: NonEmpty a) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680610119 :: NonEmpty a) = ToList a6989586621680610119 | |
type family ToListSym1 (a6989586621680610119 :: NonEmpty a) :: [a] where ... Source #
Equations
| ToListSym1 a6989586621680610119 = ToList a6989586621680610119 |
data NonEmpty_Sym0 :: (~>) [a] (Maybe (NonEmpty a)) Source #
Instances
| SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods sing :: Sing NonEmpty_Sym0 # | |
| SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # | |
Defined in Data.List.NonEmpty.Singletons Methods suppressUnusedWarnings :: () # | |
| type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621680610202 :: [a]) Source # | |
Defined in Data.List.NonEmpty.Singletons type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621680610202 :: [a]) = NonEmpty_ a6989586621680610202 | |
type family NonEmpty_Sym1 (a6989586621680610202 :: [a]) :: Maybe (NonEmpty a) where ... Source #
Equations
| NonEmpty_Sym1 a6989586621680610202 = NonEmpty_ a6989586621680610202 |
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 (a6989586621680610222 :: NonEmpty Bool) Source # | |
Defined in Data.List.NonEmpty.Singletons | |
Orphan instances
| PMonadZip NonEmpty Source # | |
| SMonadZip NonEmpty Source # | |
Methods sMzip :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply MzipSym0 t1) t2) Source # sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply MzipWithSym0 t1) t2) t3) Source # sMunzip :: forall a b (t :: NonEmpty (a, b)). Sing t -> Sing (Apply MunzipSym0 t) Source # | |