multi-containers-0.2: A few multimap variants.
MaintainerZiyang Liu <free@cofree.io>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Multimap.Table.Internal

Description

 
Synopsis

Documentation

newtype Table r c a Source #

Constructors

Table (Map r (Map c a), Map c (Map r a), Size) 

Instances

Instances details
Functor (Table r c) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

fmap :: (a -> b) -> Table r c a -> Table r c b #

(<$) :: a -> Table r c b -> Table r c a #

Foldable (Table r c) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

fold :: Monoid m => Table r c m -> m #

foldMap :: Monoid m => (a -> m) -> Table r c a -> m #

foldMap' :: Monoid m => (a -> m) -> Table r c a -> m #

foldr :: (a -> b -> b) -> b -> Table r c a -> b #

foldr' :: (a -> b -> b) -> b -> Table r c a -> b #

foldl :: (b -> a -> b) -> b -> Table r c a -> b #

foldl' :: (b -> a -> b) -> b -> Table r c a -> b #

foldr1 :: (a -> a -> a) -> Table r c a -> a #

foldl1 :: (a -> a -> a) -> Table r c a -> a #

toList :: Table r c a -> [a] #

null :: Table r c a -> Bool #

length :: Table r c a -> Int #

elem :: Eq a => a -> Table r c a -> Bool #

maximum :: Ord a => Table r c a -> a #

minimum :: Ord a => Table r c a -> a #

sum :: Num a => Table r c a -> a #

product :: Num a => Table r c a -> a #

(Ord r, Ord c) => Traversable (Table r c) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Table r c a -> f (Table r c b) #

sequenceA :: Applicative f => Table r c (f a) -> f (Table r c a) #

mapM :: Monad m => (a -> m b) -> Table r c a -> m (Table r c b) #

sequence :: Monad m => Table r c (m a) -> m (Table r c a) #

(Eq r, Eq c, Eq a) => Eq (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

(==) :: Table r c a -> Table r c a -> Bool #

(/=) :: Table r c a -> Table r c a -> Bool #

(Data r, Data c, Data a, Ord c, Ord r) => Data (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

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

gunfold :: (forall b r0. Data b => c0 (b -> r0) -> c0 r0) -> (forall r1. r1 -> c0 r1) -> Constr -> c0 (Table r c a) #

toConstr :: Table r c a -> Constr #

dataTypeOf :: Table r c a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Table r c a -> Table r c a #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> Table r c a -> r0 #

gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> Table r c a -> r0 #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Table r c a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Table r c a -> m (Table r c a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Table r c a -> m (Table r c a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Table r c a -> m (Table r c a) #

(Ord r, Ord c, Ord a) => Ord (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

compare :: Table r c a -> Table r c a -> Ordering #

(<) :: Table r c a -> Table r c a -> Bool #

(<=) :: Table r c a -> Table r c a -> Bool #

(>) :: Table r c a -> Table r c a -> Bool #

(>=) :: Table r c a -> Table r c a -> Bool #

max :: Table r c a -> Table r c a -> Table r c a #

min :: Table r c a -> Table r c a -> Table r c a #

(Ord r, Ord c, Read r, Read c, Read a) => Read (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

readsPrec :: Int -> ReadS (Table r c a) #

readList :: ReadS [Table r c a] #

readPrec :: ReadPrec (Table r c a) #

readListPrec :: ReadPrec [Table r c a] #

(Show r, Show c, Show a) => Show (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

showsPrec :: Int -> Table r c a -> ShowS #

show :: Table r c a -> String #

showList :: [Table r c a] -> ShowS #

(Ord r, Ord c) => Semigroup (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

(<>) :: Table r c a -> Table r c a -> Table r c a #

sconcat :: NonEmpty (Table r c a) -> Table r c a #

stimes :: Integral b => b -> Table r c a -> Table r c a #

(Ord r, Ord c) => Monoid (Table r c a) Source # 
Instance details

Defined in Data.Multimap.Table.Internal

Methods

mempty :: Table r c a #

mappend :: Table r c a -> Table r c a -> Table r c a #

mconcat :: [Table r c a] -> Table r c a #

type Size = Int Source #

Construction

empty :: Table r c a Source #

O(1). The empty table.

size empty === 0

singleton :: r -> c -> a -> Table r c a Source #

O(1). A table with a single element.

singleton 1 'a' "a" === fromList [(1,'a',"a")]
size (singleton 1 'a' "a") === 1

fromRowMap :: (Ord r, Ord c) => Map r (Map c a) -> Table r c a Source #

Build a table from a row map.

fromRowMap (Map.fromList [(1, Map.fromList [('a',"b"),('b',"c")]), (2, Map.fromList [('a',"d")])])
  === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]

fromColumnMap :: (Ord r, Ord c) => Map c (Map r a) -> Table r c a Source #

Build a table from a column map.

fromColumnMap (Map.fromList [(1, Map.fromList [('a',"b"),('b',"c")]), (2, Map.fromList [('a',"d")])])
  === fromList [('a',1,"b"),('a',2,"d"),('b',1,"c")]

transpose :: Table r c a -> Table c r a Source #

Flip the row and column keys.

transpose (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [('a',1,"b"),('a',2,"d"),('b',1,"c")]

From Unordered Lists

fromList :: (Ord r, Ord c) => [(r, c, a)] -> Table r c a Source #

Build a table from a list of key/value pairs.

fromList ([] :: [(Int, Char, String)]) === empty

Deletion/Update

insert :: (Ord r, Ord c) => r -> c -> a -> Table r c a -> Table r c a Source #

O(log k). Associate with value with the row key and the column key. If the table already contains a value for those keys, the value is replaced.

insert 1 'a' "a" empty === singleton 1 'a' "a"
insert 1 'a' "a" (fromList [(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'a',"a"),(1,'b',"c"),(2,'a',"d")]
insert 1 'a' "a" (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'a',"a"),(1,'b',"c"),(2,'a',"d")]

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

O(log k). Remove the value associated with the given keys.

delete 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'b',"c"),(2,'a',"d")]
delete 1 'a' (fromList [(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'b',"c"),(2,'a',"d")]

deleteRow :: Ord r => r -> Table r c a -> Table r c a Source #

Remove an entire row.

deleteRow 1 (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 2 'a' "d"
deleteRow 3 (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]

deleteColumn :: Ord c => c -> Table r c a -> Table r c a Source #

Remove an entire column.

deleteColumn 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 1 'b' "c"
deleteColumn 'z' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]

adjust :: (Ord r, Ord c) => (a -> a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function a -> a takes O(1). Update the value at a specific row key and column key, if exists.

adjust ("new " ++) 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === fromList [(1,'a',"new b"),(1,'b',"c"),(2,'a',"d")]

adjustWithKeys :: (Ord r, Ord c) => (r -> c -> a -> a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function r -> c -> a -> a takes O(1). Update the value at a specific row key and column key, if exists.

adjustWithKeys (\r c x -> show r ++ ":" ++ show c ++ ":new " ++ x) 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")])
  === fromList [(1,'a',"1:'a':new b"),(1,'b',"c"),(2,'a',"d")]

update :: (Ord r, Ord c) => (a -> Maybe a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function a -> Maybe a takes O(1). The expression (update f r c table) updates the value at the given row and column keys, if exists. If f returns Nothing, the value associated with those keys, if exists is deleted.

let f x = if x == "b" then Just "new b" else Nothing in do
  update f 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"new b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  update f 1 'a' (fromList [(1,'a',"a"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]

updateWithKeys :: (Ord r, Ord c) => (r -> c -> a -> Maybe a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function r -> c -> a -> Maybe a takes O(1). The expression (updateWithKeys f r c table) updates the value at the given row and column keys, if exists. If f returns Nothing, the value associated with those keys, if exists is deleted.

let f r c x = if x == "b" then Just (show r ++ ":" ++ show c ++ ":new b") else Nothing in do
  updateWithKeys f 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"1:'a':new b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  updateWithKeys f 1 'a' (fromList [(1,'a',"a"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]

alter :: (Ord r, Ord c) => (Maybe a -> Maybe a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function Maybe a -> Maybe a takes O(1). The expression (alter f r c table) alters the value at the given row and column keys, if exists. It can be used to insert, delete or update a value.

let (f,g,h) = (const Nothing, const (Just "hello"), fmap ('z':)) in do
  alter f 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alter f 4 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alter f 2 'b' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alter g 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"hello"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alter g 4 'e' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c"),(4,'e',"hello")]
  alter h 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"zb"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alter h 2 'b' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]

alterWithKeys :: (Ord r, Ord c) => (r -> c -> Maybe a -> Maybe a) -> r -> c -> Table r c a -> Table r c a Source #

O(log k), assuming the function r -> c -> Maybe a -> Maybe a takes O(1). The expression (alterWithKeys f r c table) alters the value at the given row and column keys, if exists. It can be used to insert, delete or update a value.

let (f,g) = (\_ _ _ -> Nothing, \r c -> fmap ((show r ++ ":" ++ show c ++ ":") ++)) in do
  alterWithKeys f 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alterWithKeys f 4 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alterWithKeys f 2 'b' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alterWithKeys g 1 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"1:'a':b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]
  alterWithKeys g 2 'b' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]) === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(3,'a',"c")]

Query

Lookup

lookup :: (Ord r, Ord c) => r -> c -> Table r c a -> Maybe a Source #

O(log k). Lookup the values at a row key and column key in the map.

(!?) :: (Ord r, Ord c) => Table r c a -> (r, c) -> Maybe a infixl 9 Source #

O(log k). Lookup the values at a row key and column key in the map.

fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")] !? (1,'a') === Just "b"
fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")] !? (1,'c') === Nothing

(!) :: (Ord r, Ord c) => Table r c a -> (r, c) -> a infixl 9 Source #

O(log k). Lookup the values at a row key and column key in the map. Calls error if the value does not exist.

fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")] ! (1,'a') === "b"

hasCell :: (Ord r, Ord c) => Table r c a -> (r, c) -> Bool Source #

O(log k). Is there a value associated with the given row and column keys?

hasCell (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (1,'a') === True
hasCell (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (1,'c') === False

hasRow :: Ord r => Table r c a -> r -> Bool Source #

O(log r). Is there a row with the given row key that has at least one value?

hasRow (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) 1 === True
hasRow (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) 3 === False

hasColumn :: Ord c => Table r c a -> c -> Bool Source #

O(log c). Is there a column with the given column key that has at least one value?

hasColumn (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) 'a' === True
hasColumn (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) 'c' === False

Size

null :: Table r c a -> Bool Source #

O(1). Is the table empty?

Data.Multimap.Table.null empty === True
Data.Multimap.Table.null (singleton 1 'a' "a") === False

notNull :: Table r c a -> Bool Source #

O(1). Is the table non-empty?

notNull empty === False
notNull (singleton 1 'a' "a") === True

size :: Table r c a -> Int Source #

The total number of values for all row and column keys.

size is evaluated lazily. Forcing the size for the first time takes up to O(n) and subsequent forces take O(1).

size empty === 0
size (singleton 1 'a' "a") === 1
size (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) === 3

Combine

Union

union :: (Ord r, Ord c) => Table r c a -> Table r c a -> Table r c a Source #

Union two tables, preferring values from the first table upon duplicate keys.

union (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")])
  === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

unionWith :: (Ord r, Ord c) => (a -> a -> a) -> Table r c a -> Table r c a -> Table r c a Source #

Union two tables with a combining function for duplicate keys.

unionWith (++) (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")])
  === fromList [(1,'a',"bc"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

unionWithKeys :: (Ord r, Ord c) => (r -> c -> a -> a -> a) -> Table r c a -> Table r c a -> Table r c a Source #

Union two tables with a combining function for duplicate keys.

let f r c a a' = show r ++ ":" ++ show c ++ ":" ++ a ++ "|" ++ a' in do
  unionWithKeys f (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")])
    === fromList [(1,'a',"1:'a':b|c"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

unions :: (Foldable f, Ord r, Ord c) => f (Table r c a) -> Table r c a Source #

Union a number of tables, preferring values from the leftmost table upon duplicate keys.

unions [fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")], fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")]]
  === fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

unionsWith :: (Foldable f, Ord r, Ord c) => (a -> a -> a) -> f (Table r c a) -> Table r c a Source #

Union a number of tables with a combining function for duplicate keys.

unionsWith (++) [fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")], fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")]]
  === fromList [(1,'a',"bc"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

unionsWithKeys :: (Foldable f, Ord r, Ord c) => (r -> c -> a -> a -> a) -> f (Table r c a) -> Table r c a Source #

Union a number of tables with a combining function for duplicate keys.

let f r c a a' = show r ++ ":" ++ show c ++ ":" ++ a ++ "|" ++ a' in do
  unionsWithKeys f [fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")], fromList [(1,'a',"c"),(2,'b',"d"),(3,'c',"e")]]
    === fromList [(1,'a',"1:'a':b|c"),(1,'b',"c"),(2,'a',"b"),(2,'b',"d"),(3,'c',"e")]

Difference

difference :: (Ord r, Ord c) => Table r c a -> Table r c a -> Table r c a Source #

Difference of two tables. Return values in the first table whose row and column keys do not have an associated value in the second table.

difference (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) (fromList [(1,'a',"c"),(1,'b',"d"),(2,'b',"b")])
  === singleton 2 'a' "b"

Traversal

Map

map :: (a -> b) -> Table r c a -> Table r c b Source #

O(n), assuming the function a -> b takes O(1). Map a function over all values in the table.

Data.Multimap.Table.map (++ "x") (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) === fromList [(1,'a',"bx"),(1,'b',"cx"),(2,'a',"bx")]

mapWithKeys :: (r -> c -> a -> b) -> Table r c a -> Table r c b Source #

O(n), assuming the function r -> c -> a -> b takes O(1). Map a function over all values in the table.

mapWithKeys (\r c x -> show r ++ ":" ++ show c ++ ":" ++ x) (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")])
  === fromList [(1,'a',"1:'a':b"),(1,'b',"1:'b':c"),(2,'a',"2:'a':b")]

traverseWithKeys :: (Applicative t, Ord r, Ord c) => (r -> c -> a -> t b) -> Table r c a -> t (Table r c b) Source #

Traverse the (row key, column key, value) triples and collect the results.

let f r c a = if odd r && c > 'a' then Just (a ++ "x") else Nothing in do
  traverseWithKeys f (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"b")]) === Nothing
  traverseWithKeys f (fromList [(1,'b',"b"),(1,'c',"c"),(3,'d',"b")]) === Just (fromList [(1,'b',"bx"),(1,'c',"cx"),(3,'d',"bx")])

traverseMaybeWithKeys :: (Applicative t, Ord r, Ord c) => (r -> c -> a -> t (Maybe b)) -> Table r c a -> t (Table r c b) Source #

Traverse the (row key, column key, value) triples and collect the Just results.

Folds

foldr :: (a -> b -> b) -> b -> Table r c a -> b Source #

O(n). Fold the values in the table row by row using the given right-associative binary operator.

Data.Multimap.Table.foldr (:) "" (fromList [(1,'a','b'),(1,'b','c'),(2,'a','d')]) === "bcd"

foldl :: (a -> b -> a) -> a -> Table r c b -> a Source #

O(n). Fold the values in the table row by row using the given left-associative binary operator.

Data.Multimap.Table.foldl (flip (:)) "" (fromList [(1,'a','b'),(1,'b','c'),(2,'a','d')]) === "dcb"

foldrWithKeys :: (r -> c -> a -> b -> b) -> b -> Table r c a -> b Source #

O(n). Fold the (row key, column key value) triplets in the table row by row using the given right-associative binary operator.

let f r c a b = show r ++ ":" ++ show c ++ ":" ++ a ++ "|" ++ b in do
  foldrWithKeys f "" (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === "1:'a':b|1:'b':c|2:'a':d|"

foldlWithKeys :: (a -> r -> c -> b -> a) -> a -> Table r c b -> a Source #

O(n). Fold the (row key, column key, value) triplets in the table row by row using the given left-associative binary operator.

let f a r c b = show r ++ ":" ++ show c ++ ":" ++ b ++ "|" ++ a in do
  foldlWithKeys f "" (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === "2:'a':d|1:'b':c|1:'a':b|"

foldMapWithKeys :: Monoid m => (r -> c -> a -> m) -> Table r c a -> m Source #

O(n). Fold the (row key, column key, value) triplets in the map row by row using the given monoid.

let f r c a = show r ++ ":" ++ show c ++ ":" ++ a ++ "|" in do
  foldMapWithKeys f (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === "1:'a':b|1:'b':c|2:'a':d|"

Strict Folds

foldr' :: (a -> b -> b) -> b -> Table r c a -> b Source #

O(n). A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Data.Multimap.Table.foldr' (:) "" (fromList [(1,'a','b'),(1,'b','c'),(2,'a','d')]) === "bcd"

foldl' :: (a -> b -> a) -> a -> Table r c b -> a Source #

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Data.Multimap.Table.foldl' (flip (:)) "" (fromList [(1,'a','b'),(1,'b','c'),(2,'a','d')]) === "dcb"

foldrWithKeys' :: (r -> c -> a -> b -> b) -> b -> Table r c a -> b Source #

O(n). A strict version of foldrWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

let f r c a b = show r ++ ":" ++ show c ++ ":" ++ a ++ "|" ++ b in do
  foldrWithKeys' f "" (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === "1:'a':b|1:'b':c|2:'a':d|"

foldlWithKeys' :: (a -> r -> c -> b -> a) -> a -> Table r c b -> a Source #

O(n). A strict version of foldlWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

let f a r c b = show r ++ ":" ++ show c ++ ":" ++ b ++ "|" ++ a in do
  foldlWithKeys' f "" (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === "2:'a':d|1:'b':c|1:'a':b|"

Conversion

row :: Ord r => r -> Table r c a -> Map c a Source #

O(r). Return a mapping from column keys to values for the given row key.

row 1 (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Map.fromList [('a',"b"),('b',"c")]
row 3 (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Map.empty

column :: Ord c => c -> Table r c a -> Map r a Source #

O(c). Return a mapping from row keys to values for the given column key.

column 'a' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Map.fromList [(1,"b"),(2,"d")]
column 'c' (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Map.empty

rowMap :: Table r c a -> Map r (Map c a) Source #

Return a mapping from row keys to maps from column keys to values.

rowMap (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")])
  === Map.fromList [(1, Map.fromList [('a',"b"),('b',"c")]),(2, Map.fromList [('a',"d")])]

columnMap :: Table r c a -> Map c (Map r a) Source #

Return a mapping from column keys to maps from row keys to values.

columnMap (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")])
  === Map.fromList [('a', Map.fromList [(1,"b"),(2,"d")]),('b', Map.fromList [(1,"c")])]

rowKeys :: Table r c a -> [r] Source #

Return, in ascending order, the list of all row keys of that have at least one value in the table.

rowKeys (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [1,2]

columnKeys :: Table r c a -> [c] Source #

Return, in ascending order, the list of all column keys of that have at least one value in the table.

columnKeys (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === ['a','b']

rowKeysSet :: Table r c a -> Set r Source #

Return the set of all row keys of that have at least one value in the table.

rowKeysSet (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Set.fromList [1,2]

columnKeysSet :: Table r c a -> Set c Source #

Return the set of all column keys of that have at least one value in the table.

columnKeysSet (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === Set.fromList ['a','b']

Lists

toList :: Table r c a -> [(r, c, a)] Source #

Convert the table into a list of (row key, column key, value) triples.

toList (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]

Ordered lists

toRowAscList :: Table r c a -> [(r, c, a)] Source #

Convert the table into a list of (row key, column key, value) triples in ascending order of row keys, and ascending order of column keys with a row.

toRowAscList (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]

toColumnAscList :: Table r c a -> [(c, r, a)] Source #

Convert the table into a list of (column key, row key, value) triples in ascending order of column keys, and ascending order of row keys with a column.

toColumnAscList (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [('a',1,"b"),('a',2,"d"),('b',1,"c")]

toRowDescList :: Table r c a -> [(r, c, a)] Source #

Convert the table into a list of (row key, column key, value) triples in descending order of row keys, and descending order of column keys with a row.

toRowDescList (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [(2,'a',"d"),(1,'b',"c"),(1,'a',"b")]

toColumnDescList :: Table r c a -> [(c, r, a)] Source #

Convert the table into a list of (column key, row key, value) triples in descending order of column keys, and descending order of row keys with a column.

toColumnDescList (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === [('b',1,"c"),('a',2,"d"),('a',1,"b")]

Filter

filter :: (a -> Bool) -> Table r c a -> Table r c a Source #

O(n), assuming the predicate function takes O(1). Retain all values that satisfy the predicate.

Data.Multimap.Table.filter (> "c") (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 2 'a' "d"
Data.Multimap.Table.filter (> "d") (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === empty

filterRow :: (r -> Bool) -> Table r c a -> Table r c a Source #

O(r), assuming the predicate function takes O(1). Retain all rows that satisfy the predicate.

filterRow even (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 2 'a' "d"

filterColumn :: (c -> Bool) -> Table r c a -> Table r c a Source #

O(c), assuming the predicate function takes O(1). Retain all columns that satisfy the predicate.

filterColumn (> 'a') (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 1 'b' "c"

filterWithKeys :: (r -> c -> a -> Bool) -> Table r c a -> Table r c a Source #

O(c), assuming the predicate function takes O(1). Retain all (row key, column key, value) triples that satisfy the predicate.

filterWithKeys (\r c a -> odd r && c > 'a' && a > "b") (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 1 'b' "c"

mapMaybe :: (a -> Maybe b) -> Table r c a -> Table r c b Source #

O(n), assuming the function a -> Maybe b takes O(1). Map values and collect the Just results.

mapMaybe (\a -> if a == "a" then Just "new a" else Nothing) (fromList [(1,'a',"a"),(1,'b',"c"),(2,'b',"a")])
  === fromList [(1,'a',"new a"),(2,'b',"new a")]

mapMaybeWithKeys :: (r -> c -> a -> Maybe b) -> Table r c a -> Table r c b Source #

O(n), assuming the function r -> c -> a -> Maybe b takes O(1). Map (row key, column key, value) triples and collect the Just results.

let f r c a = if r == 1 && a == "c" then Just "new c" else Nothing in do
  mapMaybeWithKeys f (fromList [(1,'a',"b"),(1,'b',"c"),(2,'a',"d")]) === singleton 1 'b' "new c"

mapEither :: (a -> Either a1 a2) -> Table r c a -> (Table r c a1, Table r c a2) Source #

O(n), assuming the function a -> Either a1 a2 takes O(1). Map values and separate the Left and Right results.

mapEither (\a -> if a == "a" then Left a else Right a) (fromList [(1,'a',"a"),(1,'b',"c"),(2,'b',"a")])
  === (fromList [(1,'a',"a"),(2,'b',"a")],fromList [(1,'b',"c")])

mapEitherWithKeys :: (r -> c -> a -> Either a1 a2) -> Table r c a -> (Table r c a1, Table r c a2) Source #

O(n), assuming the function r -> c -> a -> Either a1 a2 takes O(1). Map (row key, column key, value) triples and separate the Left and Right results.

mapEitherWithKeys (\r c a -> if r == 1 && c == 'a' then Left a else Right a) (fromList [(1,'a',"a"),(1,'b',"c"),(2,'b',"a")])
  === (fromList [(1,'a',"a")],fromList [(1,'b',"c"),(2,'b',"a")])