non-empty-0.3.0.1: List-like structures with static restrictions on the number of elements

Safe HaskellSafe
LanguageHaskell98

Data.NonEmpty.Class

Synopsis

Documentation

class Empty f where Source #

Minimal complete definition

empty

Methods

empty :: f a Source #

Instances
Empty [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

empty :: [a] Source #

Empty Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

empty :: Maybe a Source #

Empty Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

empty :: Seq a Source #

Empty Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

empty :: Set a Source #

Empty T Source # 
Instance details

Defined in Data.Empty

Methods

empty :: T a Source #

Empty (Map k) Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

empty :: Map k a Source #

Empty (T f) Source # 
Instance details

Defined in Data.Optional

Methods

empty :: T f a Source #

class Cons f where Source #

Minimal complete definition

cons

Methods

cons :: a -> f a -> f a infixr 5 Source #

Instances
Cons [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

cons :: a -> [a] -> [a] Source #

Cons Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

cons :: a -> Seq a -> Seq a Source #

Cons f => Cons (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

cons :: a -> T f a -> T f a Source #

(Cons f, Empty f) => Cons (T f) Source # 
Instance details

Defined in Data.Optional

Methods

cons :: a -> T f a -> T f a Source #

class Snoc f where Source #

Minimal complete definition

snoc

Methods

snoc :: f a -> a -> f a Source #

Instances
Snoc [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

snoc :: [a] -> a -> [a] Source #

Snoc Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

snoc :: Seq a -> a -> Seq a Source #

Snoc f => Snoc (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

snoc :: T f a -> a -> T f a Source #

snocDefault :: (Cons f, Traversable f) => f a -> a -> f a Source #

class ViewL f where Source #

Minimal complete definition

viewL

Methods

viewL :: f a -> Maybe (a, f a) Source #

Instances
ViewL [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewL :: [a] -> Maybe (a, [a]) Source #

ViewL Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewL :: Maybe a -> Maybe (a, Maybe a) Source #

ViewL Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewL :: Seq a -> Maybe (a, Seq a) Source #

ViewL Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewL :: Set a -> Maybe (a, Set a) Source #

ViewL T Source # 
Instance details

Defined in Data.Empty

Methods

viewL :: T a -> Maybe (a, T a) Source #

ViewL f => ViewL (T f) Source #

Caution: viewL (NonEmpty.Cons x []) = Nothing because the tail is empty, and thus cannot be NonEmpty!

This instance mainly exist to allow cascaded applications of fetch.

Instance details

Defined in Data.NonEmptyPrivate

Methods

viewL :: T f a -> Maybe (a, T f a) Source #

class ViewR f where Source #

Minimal complete definition

viewR

Methods

viewR :: f a -> Maybe (f a, a) Source #

Instances
ViewR [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewR :: [a] -> Maybe ([a], a) Source #

ViewR Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewR :: Maybe a -> Maybe (Maybe a, a) Source #

ViewR Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewR :: Seq a -> Maybe (Seq a, a) Source #

ViewR Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

viewR :: Set a -> Maybe (Set a, a) Source #

ViewR T Source # 
Instance details

Defined in Data.Empty

Methods

viewR :: T a -> Maybe (T a, a) Source #

class (ViewL f, ViewR f) => View f Source #

Instances
View [] Source # 
Instance details

Defined in Data.NonEmpty.Class

View Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

View Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

View Set Source # 
Instance details

Defined in Data.NonEmpty.Class

View T Source # 
Instance details

Defined in Data.Empty

viewRDefault :: (ViewL f, Traversable f) => f a -> Maybe (f a, a) Source #

class Singleton f where Source #

Minimal complete definition

singleton

Methods

singleton :: a -> f a Source #

Instances
Singleton [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

singleton :: a -> [a] Source #

Singleton Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

singleton :: a -> Maybe a Source #

Singleton Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

singleton :: a -> Seq a Source #

Singleton Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

singleton :: a -> Set a Source #

Empty f => Singleton (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

singleton :: a -> T f a Source #

class Append f where Source #

Minimal complete definition

append

Methods

append :: f a -> f a -> f a infixr 5 Source #

Instances
Append [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

append :: [a] -> [a] -> [a] Source #

Append Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

append :: Seq a -> Seq a -> Seq a Source #

(Cons f, Append f) => Append (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

append :: T f a -> T f a -> T f a Source #

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

Minimal complete definition

zipWith

Methods

zipWith :: (a -> b -> c) -> f a -> f b -> f c Source #

Instances
Zip [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

Zip Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

zipWith :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

Zip Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

Zip T Source # 
Instance details

Defined in Data.Empty

Methods

zipWith :: (a -> b -> c) -> T a -> T b -> T c Source #

Zip f => Zip (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

zipWith :: (a -> b -> c) -> T f a -> T f b -> T f c Source #

Zip f => Zip (T f) Source # 
Instance details

Defined in Data.Optional

Methods

zipWith :: (a -> b -> c) -> T f a -> T f b -> T f c Source #

zipWith3 :: Zip f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #

zipWith4 :: Zip f => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e Source #

zip :: Zip f => f a -> f b -> f (a, b) Source #

zip3 :: Zip f => f a -> f b -> f c -> f (a, b, c) Source #

zip4 :: Zip f => f a -> f b -> f c -> f d -> f (a, b, c, d) Source #

class Repeat f where Source #

Minimal complete definition

repeat

Methods

repeat :: a -> f a Source #

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.

Instances
Repeat [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

repeat :: a -> [a] Source #

Repeat Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

repeat :: a -> Maybe a Source #

Repeat T Source # 
Instance details

Defined in Data.Empty

Methods

repeat :: a -> T a Source #

Repeat f => Repeat (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

repeat :: a -> T f a Source #

Repeat f => Repeat (T f) Source # 
Instance details

Defined in Data.Optional

Methods

repeat :: a -> T f a Source #

class Repeat f => Iterate f where Source #

Minimal complete definition

iterate

Methods

iterate :: (a -> a) -> a -> f a Source #

Instances
Iterate [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

iterate :: (a -> a) -> a -> [a] Source #

Iterate Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

iterate :: (a -> a) -> a -> Maybe a Source #

Iterate T Source # 
Instance details

Defined in Data.Empty

Methods

iterate :: (a -> a) -> a -> T a Source #

Iterate f => Iterate (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

iterate :: (a -> a) -> a -> T f a Source #

Iterate f => Iterate (T f) Source # 
Instance details

Defined in Data.Optional

Methods

iterate :: (a -> a) -> a -> T f a Source #

class Sort f where Source #

We need to distinguish between Sort and SortBy, since there is an instance Sort Set but there cannot be an instance SortBy Set.

Minimal complete definition

sort

Methods

sort :: Ord a => f a -> f a Source #

Instances
Sort [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sort :: Ord a => [a] -> [a] Source #

Sort Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sort :: Ord a => Maybe a -> Maybe a Source #

Sort Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sort :: Ord a => Seq a -> Seq a Source #

Sort Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sort :: Ord a => Set a -> Set a Source #

Sort T Source # 
Instance details

Defined in Data.Empty

Methods

sort :: Ord a => T a -> T a Source #

(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).

Instance details

Defined in Data.NonEmptyPrivate

Methods

sort :: Ord a => T f a -> T f a Source #

(Insert f, Sort f) => Sort (T f) Source # 
Instance details

Defined in Data.Optional

Methods

sort :: Ord a => T f a -> T f a Source #

sortDefault :: (Ord a, SortBy f) => f a -> f a Source #

Default implementation for sort based on sortBy.

class Sort f => SortBy f where Source #

Minimal complete definition

sortBy

Methods

sortBy :: (a -> a -> Ordering) -> f a -> f a Source #

Instances
SortBy [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sortBy :: (a -> a -> Ordering) -> [a] -> [a] Source #

SortBy Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sortBy :: (a -> a -> Ordering) -> Maybe a -> Maybe a Source #

SortBy Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a Source #

SortBy T Source # 
Instance details

Defined in Data.Empty

Methods

sortBy :: (a -> a -> Ordering) -> T a -> T a Source #

(SortBy f, InsertBy f) => SortBy (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

sortBy :: (a -> a -> Ordering) -> T f a -> T f a Source #

(InsertBy f, SortBy f) => SortBy (T f) Source # 
Instance details

Defined in Data.Optional

Methods

sortBy :: (a -> a -> Ordering) -> T f a -> T f a Source #

class Reverse f where Source #

Minimal complete definition

reverse

Methods

reverse :: f a -> f a Source #

Instances
Reverse [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

reverse :: [a] -> [a] Source #

Reverse Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

reverse :: Maybe a -> Maybe a Source #

Reverse Seq Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

reverse :: Seq a -> Seq a Source #

Reverse T Source # 
Instance details

Defined in Data.Empty

Methods

reverse :: T a -> T a Source #

(Traversable f, Reverse f) => Reverse (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

reverse :: T f a -> T f a Source #

(Traversable f, Reverse f) => Reverse (T f) Source # 
Instance details

Defined in Data.Optional

Methods

reverse :: T f a -> T f a Source #

class Show f where Source #

Minimal complete definition

showsPrec

Methods

showsPrec :: Show a => Int -> f a -> ShowS Source #

Instances
Show [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

showsPrec :: Show a => Int -> [a] -> ShowS Source #

Show Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

showsPrec :: Show a => Int -> Set a -> ShowS Source #

Show T Source # 
Instance details

Defined in Data.Empty

Methods

showsPrec :: Show a => Int -> T a -> ShowS Source #

Show f => Show (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

showsPrec :: Show a => Int -> T f a -> ShowS Source #

Show f => Show (T f) Source # 
Instance details

Defined in Data.Optional

Methods

showsPrec :: Show a => Int -> T f a -> ShowS Source #

class Arbitrary f where Source #

Minimal complete definition

arbitrary, shrink

Methods

arbitrary :: Arbitrary a => Gen (f a) Source #

shrink :: Arbitrary a => f a -> [f a] Source #

Instances
Arbitrary [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

arbitrary :: Arbitrary a => Gen [a] Source #

shrink :: Arbitrary a => [a] -> [[a]] Source #

Arbitrary f => Arbitrary (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

arbitrary :: Arbitrary a => Gen (T f a) Source #

shrink :: Arbitrary a => T f a -> [T f a] Source #

class NFData f where Source #

Minimal complete definition

rnf

Methods

rnf :: NFData a => f a -> () Source #

Instances
NFData [] Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

rnf :: NFData a => [a] -> () Source #

NFData Maybe Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

rnf :: NFData a => Maybe a -> () Source #

NFData Set Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

rnf :: NFData a => Set a -> () Source #

NFData T Source # 
Instance details

Defined in Data.Empty

Methods

rnf :: NFData a => T a -> () Source #

NFData T Source # 
Instance details

Defined in Data.NonEmpty.Set

Methods

rnf :: NFData a => T a -> () Source #

NFData k => NFData (Map k) Source # 
Instance details

Defined in Data.NonEmpty.Class

Methods

rnf :: NFData a => Map k a -> () Source #

NFData f => NFData (T f) Source # 
Instance details

Defined in Data.NonEmptyPrivate

Methods

rnf :: NFData a => T f a -> () Source #

NFData k => NFData (T k) Source # 
Instance details

Defined in Data.NonEmpty.Map

Methods

rnf :: NFData a => T k a -> () Source #

NFData f => NFData (T f) Source # 
Instance details

Defined in Data.Optional

Methods

rnf :: NFData a => T f a -> () Source #

NFData f => NFData (T f) Source # 
Instance details

Defined in Data.Zip

Methods

rnf :: NFData a => T f a -> () Source #

(NFData f, NFData g) => NFData (T f g) Source # 
Instance details

Defined in Data.Append

Methods

rnf :: NFData a => T f g a -> () Source #