nonempty-containers-0.2.0.0: Non-empty variants of containers data types, with full API

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Sequence.NonEmpty.Internal

Description

Unsafe internal-use functions used in the implementation of Data.Sequence.NonEmpty. These functions can potentially be used to break the abstraction of NESeq and produce unsound sequences, so be wary!

Synopsis

Documentation

data NESeq a infixr 5 Source #

A general-purpose non-empty (by construction) finite sequence type.

Non-emptiness means that:

  • Functions that take an NESeq can safely operate on it with the assumption that it has at least value.
  • Functions that return an NESeq provide an assurance that the result has at least one value.

Data.Sequence.NonEmpty re-exports the API of Data.Sequence, faithfully reproducing asymptotics, typeclass constraints, and semantics. Functions that ensure that input and output maps are both non-empty (like <|) return NESeq, but functions that might potentially return an empty map (like tail) return a Seq instead.

You can directly construct an NESeq with the API from Data.Sequence.NonEmpty; it's more or less the same as constructing a normal Seq, except you don't have access to empty. There are also a few ways to construct an NESeq from a Seq:

  1. The nonEmptySeq smart constructor will convert a Seq a into a Maybe (NESeq a), returning Nothing if the original Seq was empty.
  2. You can use :<||, :||>, and insertSeqAt to insert a value into a Seq to create a guaranteed NESeq.
  3. You can use the IsNonEmpty and IsEmpty patterns to "pattern match" on a Seq to reveal it as either containing a NESeq or an empty sequence.
  4. withNonEmpty offers a continuation-based interface for deconstructing a Seq and treating it as if it were an NESeq.

You can convert an NESeq into a Seq with toSeq or IsNonEmpty, essentially "obscuring" the non-empty property from the type.

Constructors

NESeq infixr 5 

Fields

Instances
Monad NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

(>>=) :: NESeq a -> (a -> NESeq b) -> NESeq b #

(>>) :: NESeq a -> NESeq b -> NESeq b #

return :: a -> NESeq a #

fail :: String -> NESeq a #

Functor NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

MonadFix NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

mfix :: (a -> NESeq a) -> NESeq a #

Applicative NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

pure :: a -> NESeq a #

(<*>) :: NESeq (a -> b) -> NESeq a -> NESeq b #

liftA2 :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c #

(*>) :: NESeq a -> NESeq b -> NESeq b #

(<*) :: NESeq a -> NESeq b -> NESeq a #

Foldable NESeq Source #

foldr1, foldl1, maximum, and minimum are all total, unlike for Seq.

Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

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

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

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

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

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

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

toList :: NESeq a -> [a] #

null :: NESeq a -> Bool #

length :: NESeq a -> Int #

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

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

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

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

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

Traversable NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

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

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

Eq1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

liftEq :: (a -> b -> Bool) -> NESeq a -> NESeq b -> Bool #

Ord1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> NESeq a -> NESeq b -> Ordering #

Read1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NESeq a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NESeq a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NESeq a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NESeq a] #

Show1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NESeq a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NESeq a] -> ShowS #

MonadZip NESeq Source #
mzipWith = zipWith
munzip = unzip
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

mzip :: NESeq a -> NESeq b -> NESeq (a, b) #

mzipWith :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c #

munzip :: NESeq (a, b) -> (NESeq a, NESeq b) #

Comonad NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

extract :: NESeq a -> a #

duplicate :: NESeq a -> NESeq (NESeq a) #

extend :: (NESeq a -> b) -> NESeq a -> NESeq b #

Traversable1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

Foldable1 NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

toNonEmpty :: NESeq a -> NonEmpty a #

Alt NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

(<!>) :: NESeq a -> NESeq a -> NESeq a #

some :: Applicative NESeq => NESeq a -> NESeq [a] #

many :: Applicative NESeq => NESeq a -> NESeq [a] #

Apply NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

(<.>) :: NESeq (a -> b) -> NESeq a -> NESeq b #

(.>) :: NESeq a -> NESeq b -> NESeq b #

(<.) :: NESeq a -> NESeq b -> NESeq a #

liftF2 :: (a -> b -> c) -> NESeq a -> NESeq b -> NESeq c #

Bind NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

(>>-) :: NESeq a -> (a -> NESeq b) -> NESeq b #

join :: NESeq (NESeq a) -> NESeq a #

Extend NESeq Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

duplicated :: NESeq a -> NESeq (NESeq a) #

extended :: (NESeq a -> b) -> NESeq a -> NESeq b #

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

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

Data a => Data (NESeq a) Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NESeq a -> c (NESeq a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NESeq a) #

toConstr :: NESeq a -> Constr #

dataTypeOf :: NESeq a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NESeq a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NESeq a)) #

gmapT :: (forall b. Data b => b -> b) -> NESeq a -> NESeq a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NESeq a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NESeq a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NESeq a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NESeq a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NESeq a -> m (NESeq a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NESeq a -> m (NESeq a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NESeq a -> m (NESeq a) #

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

Defined in Data.Sequence.NonEmpty.Internal

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

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

show :: NESeq a -> String #

showList :: [NESeq a] -> ShowS #

Semigroup (NESeq a) Source # 
Instance details

Defined in Data.Sequence.NonEmpty.Internal

Methods

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

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

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

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

Defined in Data.Sequence.NonEmpty.Internal

Methods

rnf :: NESeq a -> () #

pattern (:<||) :: a -> Seq a -> NESeq a infixr 5 Source #

O(1). An abstract constructor for an NESeq that consists of a "head" a and a "tail" Seq a. Similar to :| for NonEmpty.

Can be used to match on the head and tail of an NESeq, and also used to construct an NESeq by consing an item to the beginnong of a Seq, ensuring that the result is non-empty.

pattern (:||>) :: Seq a -> a -> NESeq a infixl 5 Source #

O(1). An abstract constructor for an NESeq that consists of a "init" Seq a and a "last" a. Similar to :| for NonEmpty, but at the end of the list instead of at the beginning.

Can be used to match on the init and last of an NESeq, and also used to construct an NESeq by snocing an item to the end of a Seq, ensuring that the result is non-empty.

withNonEmpty :: r -> (NESeq a -> r) -> Seq a -> r Source #

O(log n). A general continuation-based way to consume a Seq as if it were an NESeq. withNonEmpty def f will take a Seq. If map is empty, it will evaluate to def. Otherwise, a non-empty map NESeq will be fed to the function f instead.

nonEmptySeq == withNonEmpty Nothing Just

toSeq :: NESeq a -> Seq a Source #

O(1). Convert a non-empty sequence back into a normal possibly-empty sequence, for usage with functions that expect Seq.

Can be thought of as "obscuring" the non-emptiness of the map in its type. See the IsNotEmpty pattern.

nonEmptySeq and maybe empty toSeq form an isomorphism: they are perfect structure-preserving inverses of eachother.

singleton :: a -> NESeq a Source #

\( O(1) \). A singleton sequence.

length :: NESeq a -> Int Source #

\( O(1) \). The number of elements in the sequence.

fromList :: NonEmpty a -> NESeq a Source #

\( O(n) \). Create a sequence from a finite list of elements. There is a function toNonEmpty in the opposite direction for all instances of the Foldable1 class, including NESeq.

fromFunction :: Int -> (Int -> a) -> NESeq a Source #

\( O(n) \). Convert a given sequence length and a function representing that sequence into a sequence.

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

\( O(\log n) \). replicate n x is a sequence consisting of n copies of x. Is only defined when n is positive.

index :: NESeq a -> Int -> a Source #

\( O(\log(\min(i,n-i))) \). The element at the specified position, counting from 0. The argument should thus be a non-negative integer less than the size of the sequence. If the position is out of range, index fails with an error.

xs `index` i = toList xs !! i

Caution: index necessarily delays retrieving the requested element until the result is forced. It can therefore lead to a space leak if the result is stored, unforced, in another structure. To retrieve an element immediately without forcing it, use lookup or '(!?)'.

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

\( O(1) \). Add an element to the left end of a non-empty sequence. Mnemonic: a triangle with the single element at the pointy end.

(><) :: NESeq a -> NESeq a -> NESeq a infixr 5 Source #

\( O(\log(\min(n_1,n_2))) \). Concatenate two non-empty sequences.

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

\( O(\log(\min(n_1,n_2))) \). Concatenate a non-empty sequence with a potentially empty sequence (Seq), to produce a guaranteed non-empty sequence. Mnemonic: like ><, but a pipe for the guarunteed non-empty side.

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

Defined here but hidden; intended for use with RULES pragma.

foldMapWithIndex :: Semigroup m => (Int -> a -> m) -> NESeq a -> m Source #

O(n). A generalization of foldMap1, foldMapWithIndex takes a folding function that also depends on the element's index, and applies it to every element in the sequence.

traverseWithIndex1 :: Apply f => (Int -> a -> f b) -> NESeq a -> f (NESeq b) Source #

O(n). traverseWithIndex1 is a version of traverse1 that also offers access to the index of each element.

tails :: NESeq a -> NESeq (NESeq a) Source #

\( O(n) \). Returns a sequence of all non-empty suffixes of this sequence, longest first. For example,

tails (fromList (1:|[2,3])) = fromList (fromList (1:|[2,3]) :| [fromList (2:|[3]), fromList (3:|[])])

Evaluating the \( i \)th suffix takes \( O(\log(\min(i, n-i))) \), but evaluating every suffix in the sequence takes \( O(n) \) due to sharing.

zip :: NESeq a -> NESeq b -> NESeq (a, b) Source #

\( O(\min(n_1,n_2)) \). zip takes two sequences and returns a sequence of corresponding pairs. If one input is short, excess elements are discarded from the right end of the longer sequence.

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

\( O(\min(n_1,n_2)) \). zipWith generalizes zip by zipping with the function given as the first argument, instead of a tupling function. For example, zipWith (+) is applied to two sequences to take the sequence of corresponding sums.

unzip :: NESeq (a, b) -> (NESeq a, NESeq b) Source #

Unzip a sequence of pairs.

unzip ps = ps `seq` (fmap fst ps) (fmap snd ps)

Example:

unzip $ fromList ((1,"a") :| [(2,"b"), (3,"c")]) =
  (fromList (1:|[2,3]), fromList ("a":|["b","c"]))

See the note about efficiency at unzipWith.

sortOnSeq :: Ord b => (a -> b) -> Seq a -> Seq a Source #

CPP for new functions not in old containers ---------------------------------------------

Compatibility layer for sortOn.

unstableSortOnSeq :: Ord b => (a -> b) -> Seq a -> Seq a Source #

Compatibility layer for unstableSortOn.

unzipSeq :: Seq (a, b) -> (Seq a, Seq b) Source #

Compatibility layer for unzip.

unzipWithSeq :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) Source #

Compatibility layer for unzipWith.