dlist-nonempty-0.1.2: Non-empty difference lists
Safe HaskellSafe
LanguageHaskell2010

Data.DList.NonEmpty

Description

Non-empty difference lists: a data structure for O(1) append on non-empty lists.

Synopsis

Documentation

data NonEmptyDList a where Source #

A difference list is a function that, given a list, returns the original contents of the difference list prepended to the given list.

Implemented as a newtype over [a] -> NonEmpty a.

Bundled Patterns

pattern Cons :: a -> [a] -> NonEmptyDList a

A unidirectional pattern synonym using toList in a view pattern and matching on x:xs such that you have the pattern Cons x xs

Instances

Instances details
Foldable NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

fold :: Monoid m => NonEmptyDList m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmptyDList a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmptyDList a -> m #

foldr :: (a -> b -> b) -> b -> NonEmptyDList a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmptyDList a -> b #

foldl :: (b -> a -> b) -> b -> NonEmptyDList a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmptyDList a -> b #

foldr1 :: (a -> a -> a) -> NonEmptyDList a -> a #

foldl1 :: (a -> a -> a) -> NonEmptyDList a -> a #

toList :: NonEmptyDList a -> [a] #

null :: NonEmptyDList a -> Bool #

length :: NonEmptyDList a -> Int #

elem :: Eq a => a -> NonEmptyDList a -> Bool #

maximum :: Ord a => NonEmptyDList a -> a #

minimum :: Ord a => NonEmptyDList a -> a #

sum :: Num a => NonEmptyDList a -> a #

product :: Num a => NonEmptyDList a -> a #

Traversable NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

traverse :: Applicative f => (a -> f b) -> NonEmptyDList a -> f (NonEmptyDList b) #

sequenceA :: Applicative f => NonEmptyDList (f a) -> f (NonEmptyDList a) #

mapM :: Monad m => (a -> m b) -> NonEmptyDList a -> m (NonEmptyDList b) #

sequence :: Monad m => NonEmptyDList (m a) -> m (NonEmptyDList a) #

Applicative NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Functor NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

fmap :: (a -> b) -> NonEmptyDList a -> NonEmptyDList b #

(<$) :: a -> NonEmptyDList b -> NonEmptyDList a #

Monad NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Alt NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Apply NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Bind NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Foldable1 NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

fold1 :: Semigroup m => NonEmptyDList m -> m #

foldMap1 :: Semigroup m => (a -> m) -> NonEmptyDList a -> m #

toNonEmpty :: NonEmptyDList a -> NonEmpty a #

Traversable1 NonEmptyDList Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

traverse1 :: Apply f => (a -> f b) -> NonEmptyDList a -> f (NonEmptyDList b) #

sequence1 :: Apply f => NonEmptyDList (f b) -> f (NonEmptyDList b) #

a ~ Char => IsString (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Semigroup (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

IsList (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Associated Types

type Item (NonEmptyDList a) #

Read a => Read (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Show a => Show (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

NFData a => NFData (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Methods

rnf :: NonEmptyDList a -> () #

Eq a => Eq (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

Ord a => Ord (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

type Item (NonEmptyDList a) Source # 
Instance details

Defined in Data.DList.NonEmpty.Internal

type Item (NonEmptyDList a) = a

Conversion

toNonEmpty :: NonEmptyDList a -> NonEmpty a Source #

Convert a dlist to a non-empty list

apply :: NonEmptyDList a -> [a] -> NonEmpty a Source #

Apply a dlist to a list to get the underlying non-empty list with an extension

toList :: NonEmptyDList a -> [a] Source #

Convert a dlist to a list

toDList :: NonEmptyDList a -> DList a Source #

Convert to DList.

Note: dlist doesn't expose internals, so this have to go through list.

toEndo :: NonEmptyDList a -> Endo [a] Source #

Convert to representation of DList.

toEndo' :: NonEmptyDList a -> [a] -> [a] Source #

Convert to representation of DList.

Construction

The O(1) functions.

fromNonEmpty :: NonEmpty a -> NonEmptyDList a Source #

Convert a list to a dlist

singleton :: a -> NonEmptyDList a Source #

Create dlist with a single element

cons :: a -> NonEmptyDList a -> NonEmptyDList a infixr 9 Source #

O(1). Prepend a single element to a dlist

snoc :: NonEmptyDList a -> a -> NonEmptyDList a infixl 9 Source #

O(1). Append a single element to a dlist

append :: NonEmptyDList a -> NonEmptyDList a -> NonEmptyDList a Source #

O(1). Append dlists

Other functions

concat1 :: NonEmpty (NonEmptyDList a) -> NonEmptyDList a Source #

O(spine). Concatenate dlists

replicate :: Int -> a -> NonEmptyDList a Source #

O(n). Create a dlist of the given number of elements.

Always creates a list with at least one element.

head :: NonEmptyDList a -> a Source #

O(n). Return the head of the dlist

tail :: NonEmptyDList a -> [a] Source #

O(n). Return the tail of the dlist

unfoldr :: (b -> (a, Maybe b)) -> b -> NonEmptyDList a Source #

O(n). Unfoldr for dlists

map :: (a -> b) -> NonEmptyDList a -> NonEmptyDList b Source #

O(n). Map over difference lists.