nonempty-containers-0.3.3.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.IntSet.NonEmpty.Internal

Description

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

Synopsis

Documentation

data NEIntSet Source #

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

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

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

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

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

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

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

Constructors

NEIntSet 

Fields

Instances
Eq NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Data NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Methods

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

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

toConstr :: NEIntSet -> Constr #

dataTypeOf :: NEIntSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Read NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Show NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Semigroup NEIntSet Source #

Left-biased union

Instance details

Defined in Data.IntSet.NonEmpty.Internal

NFData NEIntSet Source # 
Instance details

Defined in Data.IntSet.NonEmpty.Internal

Methods

rnf :: NEIntSet -> () #

type Key = Int #

nonEmptySet :: IntSet -> Maybe NEIntSet Source #

O(log n). Smart constructor for an NEIntSet from a IntSet. Returns Nothing if the IntSet was originally actually empty, and Just n with an NEIntSet, if the IntSet 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 IntSet being an NEIntSet.

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

withNonEmpty Source #

Arguments

:: r

value to return if set is empty

-> (NEIntSet -> r)

function to apply if set is not empty

-> IntSet 
-> r 

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

nonEmptySet == withNonEmpty Nothing Just

toSet :: NEIntSet -> IntSet Source #

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

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.IntSet.fromList [(3,"a"), (5,"b")]

singleton :: Key -> NEIntSet Source #

O(1). Create a singleton set.

fromList :: NonEmpty Key -> NEIntSet Source #

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

toList :: NEIntSet -> NonEmpty Key Source #

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

union :: NEIntSet -> NEIntSet -> NEIntSet 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 => f NEIntSet -> NEIntSet Source #

The union of a non-empty list of sets

valid :: NEIntSet -> Bool Source #

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

insertMinSet :: Key -> IntSet -> IntSet 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 IntSet. /The precondition is not checked./

At the moment this is simply an alias for Data.IntSet.insert, but it's left here as a placeholder in case this eventually gets implemented in a more efficient way.

insertMaxSet :: Key -> IntSet -> IntSet 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 IntSet. The precondition is not checked./

At the moment this is simply an alias for Data.IntSet.insert, but it's left here as a placeholder in case this eventually gets implemented in a more efficient way.

disjointSet :: IntSet -> IntSet -> Bool Source #

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

Comptability layer for disjoint.