| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Data.NonEmpty.Class
Synopsis
- class Empty f where- empty :: f a
 
- class Cons f where- cons :: a -> f a -> f a
 
- class Snoc f where- snoc :: f a -> a -> f a
 
- snocDefault :: (Cons f, Traversable f) => f a -> a -> f a
- class ViewL f where
- class ViewR f where
- class (ViewL f, ViewR f) => View f
- viewRDefault :: (ViewL f, Traversable f) => f a -> Maybe (f a, a)
- class Singleton f where- singleton :: a -> f a
 
- class Append f where- append :: f a -> f a -> f a
 
- class Functor f => Zip f where- zipWith :: (a -> b -> c) -> f a -> f b -> f c
 
- zipWith3 :: Zip f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- zipWith4 :: Zip f => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e
- zip :: Zip f => f a -> f b -> f (a, b)
- zip3 :: Zip f => f a -> f b -> f c -> f (a, b, c)
- zip4 :: Zip f => f a -> f b -> f c -> f d -> f (a, b, c, d)
- class Repeat f where- repeat :: a -> f a
 
- class Repeat f => Iterate f where- iterate :: (a -> a) -> a -> f a
 
- class Sort f where
- sortDefault :: (Ord a, SortBy f) => f a -> f a
- class Sort f => SortBy f where
- class Sort f => SortKey f where
- sortKeyGen :: (SortBy f, Functor f, Ord b) => (a -> b) -> f a -> f a
- class Reverse f where- reverse :: f a -> f a
 
- class Show f where
- class Arbitrary f where
- class Arbitrary f => Gen f where
- class NFData f where
- class Ix f where
Documentation
Instances
| Empty Seq Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty Set Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty T Source # | |
| Defined in Data.Empty | |
| Empty Maybe Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty [] Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty (Map k) Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty (T f) Source # | |
| Defined in Data.Optional | |
snocDefault :: (Cons f, Traversable f) => f a -> a -> f a Source #
Instances
| ViewL Seq Source # | |
| ViewL Set Source # | |
| ViewL T Source # | |
| ViewL Maybe Source # | |
| ViewL [] Source # | |
| Defined in Data.NonEmpty.Class | |
| ViewL f => ViewL (T f) Source # | Caution:
 This instance mainly exist to allow cascaded applications of  | 
class (ViewL f, ViewR f) => View f Source #
Instances
| View Seq Source # | |
| Defined in Data.NonEmpty.Class | |
| View Set Source # | |
| Defined in Data.NonEmpty.Class | |
| View T Source # | |
| Defined in Data.Empty | |
| View Maybe Source # | |
| Defined in Data.NonEmpty.Class | |
| View [] Source # | |
| Defined in Data.NonEmpty.Class | |
viewRDefault :: (ViewL f, Traversable f) => f a -> Maybe (f a, a) Source #
class Singleton f where Source #
Instances
| Singleton Seq Source # | |
| Defined in Data.NonEmpty.Class | |
| Singleton Set Source # | |
| Defined in Data.NonEmpty.Class | |
| Singleton Maybe Source # | |
| Defined in Data.NonEmpty.Class | |
| Singleton [] Source # | |
| Defined in Data.NonEmpty.Class | |
| Empty f => Singleton (T f) Source # | |
| Defined in Data.NonEmptyPrivate | |
class Functor f => Zip f where Source #
It must hold:
fmap f xs = zipWith (\x _ -> f x) xs xs = zipWith (\_ x -> f x) xs xs
Methods
Create a container with as many copies as possible of a given value.
   That is, for a container with fixed size n,
   the call repeat x will generate a container with n copies of x.
We need to distinguish between Sort and SortBy,
since there is an instance Sort Set
but there cannot be an instance SortBy Set.
Instances
| Sort Seq Source # | |
| Sort Set Source # | |
| Sort T Source # | |
| Sort Maybe Source # | |
| Sort [] Source # | |
| Defined in Data.NonEmpty.Class | |
| (Sort f, InsertBy f) => Sort (T f) Source # | If you nest too many non-empty lists then the efficient merge-sort (linear-logarithmic runtime) will degenerate to an inefficient insert-sort (quadratic runtime). | 
| (Insert f, Sort f) => Sort (T f) Source # | |
sortDefault :: (Ord a, SortBy f) => f a -> f a Source #
Instances
| NFData Set Source # | |
| NFData T Source # | |
| NFData T Source # | |
| NFData Maybe Source # | |
| NFData [] Source # | |
| Defined in Data.NonEmpty.Class | |
| NFData k => NFData (Map k) Source # | |
| NFData k => NFData (T k) Source # | |
| NFData f => NFData (T f) Source # | |
| NFData f => NFData (T f) Source # | |
| NFData f => NFData (T f) Source # | |
| (NFData f, NFData g) => NFData (T f g) Source # | |
Minimal complete definition
range, (index | indexHorner), inRange
Methods
range :: Ix i => (f i, f i) -> [f i] Source #
index :: Ix i => (f i, f i) -> f i -> Int Source #
inRange :: Ix i => (f i, f i) -> f i -> Bool Source #
rangeSize :: Ix i => (f i, f i) -> Int Source #
rangeSizeIndex :: Ix i => (f i, f i) -> (Int, f i -> Int) Source #
The default implementation causes quadratic runtime
   on nested index tuple types.
   This affects the index function, too.
indexHorner :: Ix i => (f i, f i) -> Int -> f i -> Int Source #
A custom implementation of this function
   allows for an even more efficient implementation
   of index on nested NonEmpty constructors.
Instances
| Ix T Source # | |
| Defined in Data.Empty Methods range :: Ix i => (T i, T i) -> [T i] Source # index :: Ix i => (T i, T i) -> T i -> Int Source # inRange :: Ix i => (T i, T i) -> T i -> Bool Source # rangeSize :: Ix i => (T i, T i) -> Int Source # rangeSizeIndex :: Ix i => (T i, T i) -> (Int, T i -> Int) Source # indexHorner :: Ix i => (T i, T i) -> Int -> T i -> Int Source # | |
| Ix f => Ix (T f) Source # | forRange $ \b0 -> forRange $ \b1 -> forRange $ \b2 -> let b = FuncHT.unzip $ b0!:b1!:b2!:Empty.Cons in map (Ix.index b) (Ix.range b) == take (Ix.rangeSize b) [0..] | 
| Defined in Data.NonEmptyPrivate Methods range :: Ix i => (T f i, T f i) -> [T f i] Source # index :: Ix i => (T f i, T f i) -> T f i -> Int Source # inRange :: Ix i => (T f i, T f i) -> T f i -> Bool Source # rangeSize :: Ix i => (T f i, T f i) -> Int Source # rangeSizeIndex :: Ix i => (T f i, T f i) -> (Int, T f i -> Int) Source # indexHorner :: Ix i => (T f i, T f i) -> Int -> T f i -> Int Source # | |