Copyright | (C) 2016-2018 Daniel Wagner 2019 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Ryan Scott |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
An OSet
behaves much like a Set
, with all the same asymptotics, but
also remembers the order that values were inserted.
This module offers a simplified version of the Data.Set.Ordered API that assumes left-biased indices everywhere.
Synopsis
- data OSet a
- empty :: forall a. OSet a
- singleton :: a -> OSet a
- insertPre :: Ord a => a -> OSet a -> OSet a
- insertPost :: Ord a => OSet a -> a -> OSet a
- union :: forall a. Ord a => OSet a -> OSet a -> OSet a
- null :: forall a. OSet a -> Bool
- size :: forall a. OSet a -> Int
- member :: Ord a => a -> OSet a -> Bool
- notMember :: Ord a => a -> OSet a -> Bool
- delete :: Ord a => a -> OSet a -> OSet a
- filter :: Ord a => (a -> Bool) -> OSet a -> OSet a
- (\\) :: forall a. Ord a => OSet a -> OSet a -> OSet a
- intersection :: forall a. Ord a => OSet a -> OSet a -> OSet a
- type Index = Int
- lookupIndex :: Ord a => a -> OSet a -> Maybe Index
- lookupAt :: forall a. Index -> OSet a -> Maybe a
- fromList :: Ord a => [a] -> OSet a
- toAscList :: forall a. OSet a -> [a]
- toSet :: forall a. OSet a -> Set a
Documentation
An ordered set whose insertPre
, insertPost
, intersection
, and union
operations are biased towards leftmost indices when when breaking ties
between keys.
Instances
Foldable OSet Source # | |
Defined in Language.Haskell.TH.Desugar.OSet fold :: Monoid m => OSet m -> m # foldMap :: Monoid m => (a -> m) -> OSet a -> m # foldr :: (a -> b -> b) -> b -> OSet a -> b # foldr' :: (a -> b -> b) -> b -> OSet a -> b # foldl :: (b -> a -> b) -> b -> OSet a -> b # foldl' :: (b -> a -> b) -> b -> OSet a -> b # foldr1 :: (a -> a -> a) -> OSet a -> a # foldl1 :: (a -> a -> a) -> OSet a -> a # elem :: Eq a => a -> OSet a -> Bool # maximum :: Ord a => OSet a -> a # | |
Eq a => Eq (OSet a) Source # | |
(Data a, Ord a) => Data (OSet a) Source # | |
Defined in Language.Haskell.TH.Desugar.OSet gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OSet a -> c (OSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OSet a) # toConstr :: OSet a -> Constr # dataTypeOf :: OSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OSet a)) # gmapT :: (forall b. Data b => b -> b) -> OSet a -> OSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OSet a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> OSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OSet a -> m (OSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OSet a -> m (OSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OSet a -> m (OSet a) # | |
Ord a => Ord (OSet a) Source # | |
(Ord a, Read a) => Read (OSet a) Source # | |
Show a => Show (OSet a) Source # | |
Ord a => Semigroup (OSet a) Source # | |
Ord a => Monoid (OSet a) Source # | |
Trivial sets
Insertion
insertPre :: Ord a => a -> OSet a -> OSet a Source #
The element's index will be lower than the indices of the elements in the
OSet
.
insertPost :: Ord a => OSet a -> a -> OSet a Source #
The element's index will be higher than the indices of the elements in the
OSet
.
Query
Deletion
Indexing
A 0-based index, much like the indices used by lists' !!
operation. All
indices are with respect to insertion order.