Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- data NEIntSet = NEIntSet {
- neisV0 :: !Key
- neisIntSet :: !IntSet
- type Key = Int
- nonEmptySet :: IntSet -> Maybe NEIntSet
- withNonEmpty :: r -> (NEIntSet -> r) -> IntSet -> r
- toSet :: NEIntSet -> IntSet
- singleton :: Key -> NEIntSet
- fromList :: NonEmpty Key -> NEIntSet
- toList :: NEIntSet -> NonEmpty Key
- union :: NEIntSet -> NEIntSet -> NEIntSet
- unions :: Foldable1 f => f NEIntSet -> NEIntSet
- valid :: NEIntSet -> Bool
- insertMinSet :: Key -> IntSet -> IntSet
- insertMaxSet :: Key -> IntSet -> IntSet
- disjointSet :: IntSet -> IntSet -> Bool
Documentation
A non-empty (by construction) set of integers. At least one value
exists in an
at all times.NEIntSet
a
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
:
- The
nonEmptySet
smart constructor will convert a
into aIntSet
a
, returningMaybe
(NEIntSet
a)Nothing
if the originalIntSet
was empty. - You can use the
insertIntSet
family of functions to insert a value into aIntSet
to create a guaranteedNEIntSet
. - You can use the
IsNonEmpty
andIsEmpty
patterns to "pattern match" on aIntSet
to reveal it as either containing aNEIntSet
or an empty map. withNonEmpty
offers a continuation-based interface for deconstructing aIntSet
and treating it as if it were anNEIntSet
.
You can convert an NEIntSet
into a IntSet
with toSet
or
IsNonEmpty
, essentially "obscuring" the non-empty
property from the type.
NEIntSet | |
|
Instances
FromJSON NEIntSet Source # | |
Defined in Data.IntSet.NonEmpty.Internal | |
ToJSON NEIntSet Source # | |
Data NEIntSet Source # | |
Defined in Data.IntSet.NonEmpty.Internal 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 :: forall r r'. (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 # | |
Semigroup NEIntSet Source # | Left-biased union |
Read NEIntSet Source # | |
Show NEIntSet Source # | |
NFData NEIntSet Source # | |
Defined in Data.IntSet.NonEmpty.Internal | |
Eq NEIntSet Source # | |
Ord NEIntSet Source # | |
Defined in Data.IntSet.NonEmpty.Internal |
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
with an Just
nNEIntSet
, if the IntSet
was not empty.
nonEmptySet
and
form an
isomorphism: they are perfect structure-preserving inverses of
eachother.maybe
empty
toSet
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]))
:: 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
.
will take a withNonEmpty
def fIntSet
. 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
form an
isomorphism: they are perfect structure-preserving inverses of
eachother.maybe
empty
toSet
toSet (fromList ((3,"a") :| [(5,"b")])) == Data.IntSet.fromList [(3,"a"), (5,"b")]
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.
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.