compact-sequences-0.2.0.0: Stacks, queues, and deques with compact representations.

Safe HaskellTrustworthy
LanguageHaskell2010

Data.CompactSequence.Stack.Simple.Internal

Description

Space-efficient stacks with amortized \( O(\log n) \) operations. These directly use an underlying array-based implementation, without doing any special optimization for the very top of the stack.

Synopsis

Documentation

newtype Stack a Source #

A stack.

Constructors

Stack 

Fields

Bundled Patterns

pattern Empty :: Stack a

A bidirectional pattern synonym for the empty stack.

pattern (:<) :: a -> Stack a -> Stack a infixr 5

A bidirectional pattern synonym for working with the front of a stack.

Instances
Functor Stack Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

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

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

Foldable Stack Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

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

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

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

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

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

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

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

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

toList :: Stack a -> [a] #

null :: Stack a -> Bool #

length :: Stack a -> Int #

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

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

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

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

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

Traversable Stack Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

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

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

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

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

IsList (Stack a) Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Associated Types

type Item (Stack a) :: Type #

Methods

fromList :: [Item (Stack a)] -> Stack a #

fromListN :: Int -> [Item (Stack a)] -> Stack a #

toList :: Stack a -> [Item (Stack a)] #

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

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

(==) :: Stack a -> Stack a -> Bool #

(/=) :: Stack a -> Stack a -> Bool #

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

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

compare :: Stack a -> Stack a -> Ordering #

(<) :: Stack a -> Stack a -> Bool #

(<=) :: Stack a -> Stack a -> Bool #

(>) :: Stack a -> Stack a -> Bool #

(>=) :: Stack a -> Stack a -> Bool #

max :: Stack a -> Stack a -> Stack a #

min :: Stack a -> Stack a -> Stack a #

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

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

showsPrec :: Int -> Stack a -> ShowS #

show :: Stack a -> String #

showList :: [Stack a] -> ShowS #

Semigroup (Stack a) Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

(<>) :: Stack a -> Stack a -> Stack a #

sconcat :: NonEmpty (Stack a) -> Stack a #

stimes :: Integral b => b -> Stack a -> Stack a #

Monoid (Stack a) Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

Methods

mempty :: Stack a #

mappend :: Stack a -> Stack a -> Stack a #

mconcat :: [Stack a] -> Stack a #

type Item (Stack a) Source # 
Instance details

Defined in Data.CompactSequence.Stack.Simple.Internal

type Item (Stack a) = a

empty :: Stack a Source #

The empty stack.

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

Push an element onto the front of a stack.

\( O(\log n) \)

(<|) :: a -> Stack a -> Stack a infixr 5 Source #

An infix synonym for cons.

uncons :: Stack a -> Maybe (a, Stack a) Source #

Pop an element off the front of a stack.

Accessing the first element is \( O(1) \). Accessing the rest is \( O(\log n) \).

compareLength :: Int -> Stack a -> Ordering Source #

\( O(\min(m, n)) \). Compare an Int to the length of a Stack.

compareLength n xs = compare n (length xs)

take :: Int -> Stack a -> Stack a Source #

Take up to the given number of elements from the front of a stack to form a new stack. \( O(\min (k, n)) \), where \( k \) is the integer argument and \( n \) is the size of the stack.

fromList :: [a] -> Stack a Source #

\( O(n \log n) \). Convert a list to a stack, with the first element of the list as the top of the stack.

fromListN :: Int -> [a] -> Stack a Source #

\( O(n) \). Convert a list of known length to a stack, with the first element of the list as the top of the stack.