| Copyright | (C) Richard Cook 2019 |
|---|---|
| License | MIT |
| Maintainer | rcook@rcook.org |
| Stability | stable |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Data.Set.Ordered
Description
This module provides OSet, an insertion-order-preserving set, with
type class instances for Foldable, Semigroup, Monoid and Data as
well as a map function.
This is intended to be API-compatible with OSet in unordered-containers but with a few extra type class instances.
Here's the quick-start guide to using this package:
module Main (main) where
import Data.Set.Ordered ((|>), (|<))
import qualified Data.Set.Ordered as OSet
main :: IO ()
main = do
-- Create from list
let s0 = OSet.fromList [1 :: Int, 2, 3, 4, 4, 3, 2, 1, -1, -2, -3]
print s0 -- outputs: "fromList [1,2,3,4,-1,-2,-3]"
-- Append
let s1 = s0 |> 4
print s1 -- outputs: "fromList [1,2,3,4,-1,-2,-3]"
-- Prepend
let s2 = 4 |< s0
print s2 -- outputs: "fromList [4,1,2,3,-1,-2,-3]"
-- Semigroup
let s3 = s0 <> OSet.fromList [10, 10, 20, 20, 30, 30]
print s3 -- outputs: "fromList [1,2,3,4,-1,-2,-3,10,20,30]"
-- Map (but note that OSet is not a functor)
let s4 = OSet.map (\x -> x * x) s3
print s4 -- outputs: "fromList [1,4,9,16,100,400,900]"
-- Filter
let s5 = OSet.filter (>= 100) s4
print s5 -- outputs: "fromList [100,400,900]"There are cases where the developer's natural instinct would be to
convert the OSet instance to a list using toList from Foldable.
While this is possible, it will often be more efficient to use toSeq
and operate on the sequence that way. You can even use view patterns to
pattern-match on the resulting sequence:
module Main (main) where
import Data.Sequence (ViewL(..), viewl)
import Data.Set.Ordered (OSet)
import qualified Data.Set.Ordered as OSet
showFromLeft :: Show a => OSet a -> String
showFromLeft o = go (OSet.toSeq o)
where
go (viewl -> EmptyL) = ""
go (viewl -> h :< t) = show h ++ go t
go _ = error "Should not happen" -- suppress warning about non-exhaustive patterns
main :: IO ()
main = do
let a = OSet.fromList [4 :: Int, 1, 3, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9]
print $ showFromLeft a -- outputs: "4139025678"Synopsis
- data OSet a
- empty :: OSet a
- singleton :: a -> OSet a
- (<|) :: Ord a => a -> OSet a -> OSet a
- (|<) :: Ord a => a -> OSet a -> OSet a
- (>|) :: Ord a => OSet a -> a -> OSet a
- (|>) :: Ord a => OSet a -> a -> OSet a
- (<>|) :: Ord a => OSet a -> OSet a -> OSet a
- (|<>) :: Ord a => OSet a -> OSet a -> OSet a
- member :: Ord a => a -> OSet a -> Bool
- notMember :: Ord a => a -> OSet a -> Bool
- size :: OSet a -> Int
- (\\) :: Ord a => OSet a -> OSet a -> OSet a
- delete :: Ord a => a -> OSet a -> OSet a
- filter :: (a -> Bool) -> OSet a -> OSet a
- type Index = Int
- elemAt :: OSet a -> Index -> Maybe a
- findIndex :: Eq a => a -> OSet a -> Maybe Index
- fromList :: Ord a => [a] -> OSet a
- toAscList :: OSet a -> [a]
- toSeq :: OSet a -> Seq a
- map :: Ord b => (a -> b) -> OSet a -> OSet b
Documentation
An OSet behaves much like a Set but remembers the order in
which the elements were originally inserted.
Instances
| Foldable OSet Source # | |
Defined in Data.Set.Ordered Methods 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 Data.Set.Ordered Methods 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 # | |
| Show a => Show (OSet a) Source # | |
| Ord a => Semigroup (OSet a) Source # | |
| Ord a => Monoid (OSet a) Source # | |
Trivial sets
Arguments
| :: a | element |
| -> OSet a | set |
\(O(1)\). A singleton set containing the given element.
Insertion
\(O(log(N))\). Add an element to the left end of the sequence if the set does not already contain the element. Otherwise ignore the element.
\(O(log(N))\) if the element is not in the set, \(O(N)\) if the element is already in the set. Add an element to the left end of the sequence if the set does not already contain the element. Move the element to the left end of the sequence if the element is already present in the set.
\(O(log(N))\) if the element is not in the set, \(O(N)\) if the element is already in the set. Add an element to the right end of the sequence if the set does not already contain the element. Move the element to the right end of the sequence if the element is already present in the set.
\(O(log(N))\). Add an element to the right end of the sequence if the set does not already contain the element. Otherwise ignore the element.
\(O(N^2)\) worst case. Add elements from the right-hand set to the left-hand set. If elements occur in both sets, then this operation discards elements from the left-hand set and preserves those from the right.
\(O(Nlog(N))\) worst case. Add elements from the right-hand set to the left-hand set. If elements occur in both sets, then this operation discards elements from the right-hand set and preserves those from the left.
Query
\(O(log(N))\). Determine if the element is in the set.
\(O(log(N))\). Determine if the element is not in the set.
Deletion
\(O(N M)\). Find the set difference: r \\ s removes all M values in
s from r with N values.
\(O(log N)\). Delete an element from the set.
\(O(N)\). Filter a set by returning a set whose elements satisfy the predicate.
Indexing
\(O(log(min(i, N - i)))\). Return the element at the specified position,
\(i\), counting from 0. If the specified position is out of range, this
function returns Nothing.
\(O(N)\). Finds the index of the leftmost element that matches the
specified element or returns Nothing if no matching element can be found.
Conversion
\(O(N log(N))\). Create a set from a finite list of elements. If an element
occurs multiple times in the original list, only the first occurrence is
retained in the resulting set. The function toList, \(O(N)\), in Foldable
can be used to return a list of the elements in the original insert order
with duplicates removed.
Arguments
| :: OSet a | set |
| -> [a] | list |
\(O(N)\). Convert the set to an ascending list of elements.
\(O(1)\). Return ordered sequence of elements in set. For obtaining
a useful Functor instance this is recommended over toList
due to its \(O(1)\) performance. Similarly, if you want to pattern-match on
the OSet, obtain the sequence and use view patterns or pattern synonyms
instead of converting to a list.