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

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

Data.Set.NonEmpty.Internal

Description

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

Synopsis

Documentation

data NESet a Source #

A non-empty (by construction) set of values a. At least one value exists in an NESet a at all times.

Functions that take an NESet can safely operate on it with the assumption that it has at least one item.

Functions that return an NESet provide an assurance that the result has at least one item.

Data.Set.NonEmpty re-exports the API of Data.Set, faithfully reproducing asymptotics, typeclass constraints, and semantics. Functions that ensure that input and output sets are both non-empty (like insert) return NESet, but functions that might potentially return an empty map (like delete) return a Set instead.

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

  1. The nonEmptySet smart constructor will convert a Set a into a Maybe (NESet a), returning Nothing if the original Set was empty.
  2. You can use the insertSet family of functions to insert a value into a Set to create a guaranteed NESet.
  3. You can use the IsNonEmpty and IsEmpty patterns to "pattern match" on a Set to reveal it as either containing a NESet or an empty map.
  4. withNonEmpty offers a continuation-based interface for deconstructing a Set and treating it as if it were an NESet.

You can convert an NESet into a Set with toSet or IsNonEmpty, essentially "obscuring" the non-empty property from the type.

Constructors

NESet 

Fields

  • nesV0 :: !a

    invariant: must be smaller than smallest value in set

  • nesSet :: !(Set a)
     
Instances
Foldable NESet Source #

Traverses elements in ascending order

foldr1, foldl1, minimum, maximum are all total.

Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

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

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

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

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

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

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

toList :: NESet a -> [a] #

null :: NESet a -> Bool #

length :: NESet a -> Int #

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

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

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

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

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

Eq1 NESet Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

Ord1 NESet Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

Show1 NESet Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

Foldable1 NESet Source #

Traverses elements in ascending order

Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

toNonEmpty :: NESet a -> NonEmpty a #

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

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

(Data a, Ord a) => Data (NESet a) Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

toConstr :: NESet a -> Constr #

dataTypeOf :: NESet a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Set.NonEmpty.Internal

Methods

compare :: NESet a -> NESet a -> Ordering #

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

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

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

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

max :: NESet a -> NESet a -> NESet a #

min :: NESet a -> NESet a -> NESet a #

(Read a, Ord a) => Read (NESet a) Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

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

Defined in Data.Set.NonEmpty.Internal

Methods

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

show :: NESet a -> String #

showList :: [NESet a] -> ShowS #

Ord a => Semigroup (NESet a) Source #

Left-biased union

Instance details

Defined in Data.Set.NonEmpty.Internal

Methods

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

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

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

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

Defined in Data.Set.NonEmpty.Internal

Methods

rnf :: NESet a -> () #

nonEmptySet :: Set a -> Maybe (NESet a) Source #

O(log n). Smart constructor for an NESet from a Set. Returns Nothing if the Set was originally actually empty, and Just n with an NESet, if the Set was not empty.

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

See IsNonEmpty for a pattern synonym that lets you "match on" the possiblity of a Set being an NESet.

nonEmptySet (Data.Set.fromList [3,5]) == Just (fromList (3:|[5]))

withNonEmpty Source #

Arguments

:: r

value to return if set is empty

-> (NESet a -> r)

function to apply if set is not empty

-> Set a 
-> r 

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

nonEmptySet == withNonEmpty Nothing Just

toSet :: NESet a -> Set a Source #

O(log n). Convert a non-empty set back into a normal possibly-empty map, for usage with functions that expect Set.

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

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

toSet (fromList ((3,"a") :| [(5,"b")])) == Data.Set.fromList [(3,"a"), (5,"b")]

singleton :: a -> NESet a Source #

O(1). Create a singleton set.

fromList :: Ord a => NonEmpty a -> NESet a Source #

O(n*log n). Create a set from a list of elements.

toList :: NESet a -> NonEmpty a Source #

O(n). Convert the set to a non-empty list of elements.

size :: NESet a -> Int Source #

O(1). The number of elements in the set. Guaranteed to be greater than zero.

union :: Ord a => NESet a -> NESet a -> NESet a Source #

O(m*log(n/m + 1)), m <= n. The union of two sets, preferring the first set when equal elements are encountered.

unions :: (Foldable1 f, Ord a) => f (NESet a) -> NESet a Source #

The union of a non-empty list of sets

foldr :: (a -> b -> b) -> b -> NESet a -> b Source #

O(n). Fold the elements in the set using the given right-associative binary operator, such that foldr f z == foldr f z . toAscList.

For example,

elemsList set = foldr (:) [] set

foldl :: (a -> b -> a) -> a -> NESet b -> a Source #

O(n). Fold the elements in the set using the given left-associative binary operator, such that foldl f z == foldl f z . toAscList.

For example,

descElemsList set = foldl (flip (:)) [] set

foldr' :: (a -> b -> b) -> b -> NESet a -> b Source #

O(n). A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldl' :: (a -> b -> a) -> a -> NESet b -> a Source #

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

newtype MergeNESet a Source #

Constructors

MergeNESet 

Fields

Instances
Semigroup (MergeNESet a) Source # 
Instance details

Defined in Data.Set.NonEmpty.Internal

merge :: NESet a -> NESet a -> NESet a Source #

Unsafely merge two disjoint sets. Only legal if all items in the first set are less than all items in the second set

valid :: Ord a => NESet a -> Bool Source #

O(n). Test if the internal set structure is valid.

insertMinSet :: a -> Set a -> Set a Source #

O(log n). Insert new value into a set where values are strictly greater than the new values That is, the new value must be strictly less than all values present in the Set. /The precondition is not checked./

While this has the same asymptotics as Data.Set.insert, it saves a constant factor for value comparison (so may be helpful if comparison is expensive) and also does not require an Ord instance for the value type.

insertMaxSet :: a -> Set a -> Set a Source #

O(log n). Insert new value into a set where values are /strictly less than the new value. That is, the new value must be strictly greater than all values present in the Set. The precondition is not checked./

While this has the same asymptotics as Data.Set.insert, it saves a constant factor for value comparison (so may be helpful if comparison is expensive) and also does not require an Ord instance for the value type.

disjointSet :: Ord a => Set a -> Set a -> Bool Source #

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

Comptability layer for disjoint.

powerSetSet :: Set a -> Set (Set a) Source #

Comptability layer for powerSet.

disjointUnionSet :: Set a -> Set b -> Set (Either a b) Source #

Comptability layer for disjointUnion.

cartesianProductSet :: Set a -> Set b -> Set (a, b) Source #

Comptability layer for cartesianProduct.