oset-0.1.1.0: An insertion-order-preserving set

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

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

Documentation

(|>) infixl 5 Source #

Arguments

:: Ord a 
=> OSet a

set

-> a

element

-> OSet a

set

\(O(log(N))\). Append an element to the end of set if the set does not already contain the element. The element is ignored if it is already in the set.

(|<) infixr 5 Source #

Arguments

:: Ord a 
=> a

element

-> OSet a

set

-> OSet a

set

\(O(log(N))\) if the element is not in the set, \(O(N)\) if the element is already in the set. Prepend an element to the head of the set if the set does not already contain the element. The element is moved to the head of the sequence if the element is already present in the set.

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

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 #

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

Defined in Data.Set.Ordered

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

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

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

Methods

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

show :: OSet a -> String #

showList :: [OSet a] -> ShowS #

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

Defined in Data.Set.Ordered

Methods

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

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

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

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

Defined in Data.Set.Ordered

Methods

mempty :: OSet a #

mappend :: OSet a -> OSet a -> OSet a #

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

empty Source #

Arguments

:: OSet a

set

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

filter Source #

Arguments

:: (a -> Bool)

predicate

-> OSet a

set

-> OSet a

set

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

fromList Source #

Arguments

:: Ord a 
=> [a]

elements

-> OSet a

set

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

map :: Ord b => (a -> b) -> OSet a -> OSet 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.

member Source #

Arguments

:: Ord a 
=> a

element

-> OSet a

set

-> Bool

True if element is in set, False otherwise

\(O(log(N))\). Determine if the element is in the set.

notMember Source #

Arguments

:: Ord a 
=> a

element

-> OSet a

set

-> Bool

True if element is not in set, False otherwise

\(O(log(N))\). Determine if the element is not in the set.

singleton Source #

Arguments

:: a

element

-> OSet a

set

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

toSeq :: OSet a -> Seq a Source #

\(O(1)\). Return ordered sequence of elements in set. For obtaining a useful Functor this is recommended over toList due to its constant-time performance. Similarly, if you want to pattern-match on the OSet, obtain the sequence and use view patterns instead of converting to a list.