oset-0.4.0.1: An insertion-order-preserving set

Copyright(C) Richard Cook 2019
LicenseMIT
Maintainerrcook@rcook.org
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Set.Ordered

Contents

Description

This module provides OSet, an insertion-order-preserving set as well as left- and right-biased wrappers OSetL and OSetR respectively. OSet has instances for Foldable and Data as well as a map function and other features. Semigroup and Monoid type class instances are provided for OSetL and OSetR.

This is intended to be mostly API-compatible with OSet in unordered-containers but with a few extra type class instances provided via newtype wrappers.

Here's the quick-start guide to using this package:


module Main (main) where

import           Data.Set.Ordered ((|>), (|<), (|<>), OSet)
import qualified Data.Set.Ordered as OSet
import           Data.Sequence (Seq(..))

main :: IO ()
main = do
    -- Create from list
    let s0 :: OSet Int
        s0 = OSet.fromListL [1, 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]"

    -- Append
    let s3 = s0 |<> OSet.fromListL [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]"

    -- Pattern matching
    print $ foldWithPatternSynonyms (OSet.toSeq s5)

foldWithPatternSynonyms :: Show a => Seq a -> String
foldWithPatternSynonyms Empty = ""
foldWithPatternSynonyms (x :<| xs) = show x ++ foldWithPatternSynonyms xs

There are cases where the developer's natural instinct would be to convert the OSet instance to a list using toList. 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.fromListL [4 :: Int, 1, 3, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9]
    print $ showFromLeft a -- outputs: "4139025678"
Synopsis

Documentation

data OSet a Source #

An OSet behaves much like a Set but remembers the order in which the elements were originally inserted.

Instances
Foldable OSet Source # 
Instance details

Defined in Data.Set.Ordered.OSet

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 #

toList :: OSet a -> [a] #

null :: OSet a -> Bool #

length :: OSet a -> Int #

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

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

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

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

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

Ord a => PreserveR a OSet Source # 
Instance details

Defined in Data.Set.Ordered.OSet

Methods

(<|) :: a -> OSet a -> OSet a Source #

(>|) :: OSet a -> a -> OSet a Source #

(<>|) :: OSet a -> OSet a -> OSet a Source #

Ord a => PreserveL a OSet Source # 
Instance details

Defined in Data.Set.Ordered.OSet

Methods

(|<) :: a -> OSet a -> OSet a Source #

(|>) :: OSet a -> a -> OSet a Source #

(|<>) :: OSet a -> OSet a -> OSet a Source #

OrderedSet a OSet Source # 
Instance details

Defined in Data.Set.Ordered.OSet

Methods

empty :: OSet a Source #

singleton :: a -> OSet a Source #

fromListL :: [a] -> OSet a Source #

fromListR :: [a] -> OSet a Source #

member :: a -> OSet a -> Bool Source #

notMember :: a -> OSet a -> Bool Source #

map :: Ord b => (a -> b) -> OSet a -> OSet b Source #

filter :: (a -> Bool) -> OSet a -> OSet a Source #

size :: OSet a -> Int Source #

toSeq :: OSet a -> Seq a Source #

toAscList :: OSet a -> [a] Source #

findIndex :: a -> OSet a -> Maybe Index Source #

elemAt :: OSet a -> Index -> Maybe a Source #

delete :: a -> OSet a -> OSet a Source #

(\\) :: OSet a -> OSet a -> OSet a Source #

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

Defined in Data.Set.Ordered.OSet

Methods

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

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

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

Defined in Data.Set.Ordered.OSet

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 # 
Instance details

Defined in Data.Set.Ordered.OSet

Methods

compare :: OSet a -> OSet a -> Ordering #

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

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

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

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

max :: OSet a -> OSet a -> OSet a #

min :: OSet a -> OSet a -> OSet a #

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

Defined in Data.Set.Ordered.OSet

Methods

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

show :: OSet a -> String #

showList :: [OSet a] -> ShowS #

data OSetL a Source #

A left-biased OSet.

Instances
Foldable OSetL Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

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

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

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

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

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

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

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

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

toList :: OSetL a -> [a] #

null :: OSetL a -> Bool #

length :: OSetL a -> Int #

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

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

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

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

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

Ord a => PreserveL a OSetL Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

(|<) :: a -> OSetL a -> OSetL a Source #

(|>) :: OSetL a -> a -> OSetL a Source #

(|<>) :: OSetL a -> OSetL a -> OSetL a Source #

OrderedSet a OSetL Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

empty :: OSetL a Source #

singleton :: a -> OSetL a Source #

fromListL :: [a] -> OSetL a Source #

fromListR :: [a] -> OSetL a Source #

member :: a -> OSetL a -> Bool Source #

notMember :: a -> OSetL a -> Bool Source #

map :: Ord b => (a -> b) -> OSetL a -> OSetL b Source #

filter :: (a -> Bool) -> OSetL a -> OSetL a Source #

size :: OSetL a -> Int Source #

toSeq :: OSetL a -> Seq a Source #

toAscList :: OSetL a -> [a] Source #

findIndex :: a -> OSetL a -> Maybe Index Source #

elemAt :: OSetL a -> Index -> Maybe a Source #

delete :: a -> OSetL a -> OSetL a Source #

(\\) :: OSetL a -> OSetL a -> OSetL a Source #

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

Defined in Data.Set.Ordered.LR

Methods

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

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

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

Defined in Data.Set.Ordered.LR

Methods

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

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

toConstr :: OSetL a -> Constr #

dataTypeOf :: OSetL a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Set.Ordered.LR

Methods

compare :: OSetL a -> OSetL a -> Ordering #

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

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

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

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

max :: OSetL a -> OSetL a -> OSetL a #

min :: OSetL a -> OSetL a -> OSetL a #

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

Defined in Data.Set.Ordered.LR

Methods

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

show :: OSetL a -> String #

showList :: [OSetL a] -> ShowS #

Ord a => Semigroup (OSetL a) Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

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

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

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

Ord a => Monoid (OSetL a) Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

mempty :: OSetL a #

mappend :: OSetL a -> OSetL a -> OSetL a #

mconcat :: [OSetL a] -> OSetL a #

data OSetR a Source #

A right-biased OSet.

Instances
Foldable OSetR Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

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

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

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

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

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

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

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

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

toList :: OSetR a -> [a] #

null :: OSetR a -> Bool #

length :: OSetR a -> Int #

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

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

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

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

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

Ord a => PreserveR a OSetR Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

(<|) :: a -> OSetR a -> OSetR a Source #

(>|) :: OSetR a -> a -> OSetR a Source #

(<>|) :: OSetR a -> OSetR a -> OSetR a Source #

OrderedSet a OSetR Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

empty :: OSetR a Source #

singleton :: a -> OSetR a Source #

fromListL :: [a] -> OSetR a Source #

fromListR :: [a] -> OSetR a Source #

member :: a -> OSetR a -> Bool Source #

notMember :: a -> OSetR a -> Bool Source #

map :: Ord b => (a -> b) -> OSetR a -> OSetR b Source #

filter :: (a -> Bool) -> OSetR a -> OSetR a Source #

size :: OSetR a -> Int Source #

toSeq :: OSetR a -> Seq a Source #

toAscList :: OSetR a -> [a] Source #

findIndex :: a -> OSetR a -> Maybe Index Source #

elemAt :: OSetR a -> Index -> Maybe a Source #

delete :: a -> OSetR a -> OSetR a Source #

(\\) :: OSetR a -> OSetR a -> OSetR a Source #

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

Defined in Data.Set.Ordered.LR

Methods

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

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

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

Defined in Data.Set.Ordered.LR

Methods

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

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

toConstr :: OSetR a -> Constr #

dataTypeOf :: OSetR a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Set.Ordered.LR

Methods

compare :: OSetR a -> OSetR a -> Ordering #

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

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

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

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

max :: OSetR a -> OSetR a -> OSetR a #

min :: OSetR a -> OSetR a -> OSetR a #

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

Defined in Data.Set.Ordered.LR

Methods

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

show :: OSetR a -> String #

showList :: [OSetR a] -> ShowS #

Ord a => Semigroup (OSetR a) Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

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

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

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

Ord a => Monoid (OSetR a) Source # 
Instance details

Defined in Data.Set.Ordered.LR

Methods

mempty :: OSetR a #

mappend :: OSetR a -> OSetR a -> OSetR a #

mconcat :: [OSetR a] -> OSetR a #

Trivial sets

empty :: OrderedSet a c => c a Source #

\(O(1)\). The empty set.

singleton :: OrderedSet a c => a -> c a Source #

\(O(1)\). A singleton set containing the given element.

Insertion

(<|) :: PreserveR a c => a -> c a -> c a infixr 5 Source #

\(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.

(|<) :: PreserveL a c => a -> c a -> c a infixr 5 Source #

\(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.

(>|) :: PreserveR a c => c a -> a -> c a infixl 5 Source #

\(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.

(|>) :: PreserveL a c => c a -> a -> c a infixl 5 Source #

\(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.

(<>|) :: PreserveR a c => c a -> c a -> c a infixr 6 Source #

\(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.

(|<>) :: PreserveL a c => c a -> c a -> c a infixr 6 Source #

\(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

member :: (OrderedSet a c, Ord a) => a -> c a -> Bool Source #

\(O(log(N))\). Determine if the element is in the set. Evaluate to True if element is in set, False otherwise.

notMember :: (OrderedSet a c, Ord a) => a -> c a -> Bool Source #

\(O(log(N))\). Determine if the element is not in the set. Evaluate to True if element is not in set, False otherwise.

size :: OrderedSet a c => c a -> Int Source #

\(O(1)\). The number of elements in the set.

Deletion

(\\) :: (OrderedSet a c, Ord a) => c a -> c a -> c a Source #

\(O(N M)\). Find the set difference: r \\ s removes all M values in s from r with N values.

delete :: (OrderedSet a c, Ord a) => a -> c a -> c a Source #

\(O(log N)\). Delete an element from the set.

filter :: OrderedSet a c => (a -> Bool) -> c a -> c a Source #

\(O(N)\). Filter a set by returning a set whose elements satisfy the predicate.

Indexing

type Index = Int Source #

A zero-based index with respect to insertion order.

elemAt :: OrderedSet a c => c a -> Index -> Maybe a Source #

\(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.

findIndex :: (OrderedSet a c, Eq a) => a -> c a -> Maybe Index Source #

\(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

fromListL :: (OrderedSet a c, Ord a) => [a] -> c a Source #

\(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)\), can be used to return a list of the elements in the original insert order with duplicates removed.

fromListR :: (OrderedSet a c, Ord a) => [a] -> c a Source #

\(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 last occurrence is retained in the resulting set. The function toList, \(O(N)\), can be used to return a list of the elements in the original insert order with duplicates removed.

toAscList :: OrderedSet a c => c a -> [a] Source #

\(O(N)\). Convert the set to an ascending list of elements.

toSeq :: OrderedSet a c => c a -> Seq a Source #

\(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.

Miscellaneous

map :: (OrderedSet a c, Ord b) => (a -> b) -> c a -> c b Source #

\(O(N log(N))\). Return the set obtained by applying a function to each element of this set. Note that the resulting set may be smaller than the original. Along with the Ord constraint, this means that OSet cannot provide a lawful Functor instance.