Data.FiniteMap proposed addition, bug fix

At 13:06 09/11/04 +0000, Simon Marlow wrote:
On 09 November 2004 12:45, Graham Klyne wrote:
I'd like to propose an addition to the FiniteMap module in the form of a monadic version of plusFM_C. The proposed implementation is pretty much a copy of the existing implementation within a do block.
Data.FiniteMap will shortly be deprecated in favour of DData.Map (which will be renamed to Data.Map when it is imported). Perhaps you'd like to reformulate the proposal using Data.Map instead?
I added tests for the monad threading order, and realized it was a complete red herring. (I got it in my head that when reversing the parameters to optimize the hedge union, I needed to reverse the monad ordering. Duh!) So the two sets of functions for hedgeUnionWithKeyM* were unnecessary, unless it really is desired to have right-to-left monad threading #g -- Proposed addition: [[ {-------------------------------------------------------------------- Monadic union --------------------------------------------------------------------} -- | /O(n+m)/. Monadic version of union with a combining function. -- The implementation uses the efficient /hedge-union/ algorithm. -- -- The combining function returns a monadic value, which is threaded though -- the combined elements in key order, yielding a Map that is bound -- to the same monadic type. The intended use for this is with a Maybe -- monad, allowing result returned to be Nothing if any of the attempted -- combinations of key values return Nothing. Could also be usefully used -- with an error or state monad. -- unionWithM :: (Ord k, Monad m) => (a -> a -> m a) -> Map k a -> Map k a -> m (Map k a) unionWithM f m1 m2 = unionWithKeyM (\k x y -> f x y) m1 m2 -- | /O(n+m)/. Monadic version of @unionWithKey@. -- The implementation uses the efficient /hedge-union/ algorithm. -- -- See @unionWithM@ for further details. -- unionWithKeyM :: (Ord k, Monad m) => (k -> a -> a -> m a) -> Map k a -> Map k a -> m (Map k a) unionWithKeyM f Tip t2 = return t2 unionWithKeyM f t1 Tip = return t1 unionWithKeyM f t1 t2 -- hedge-union is more efficient on (bigset `union` smallset) | size t1 >= size t2 = hedgeUnionWithKeyML f (const LT) (const GT) t1 t2 | otherwise = hedgeUnionWithKeyML flipf (const LT) (const GT) t2 t1 where flipf k x y = f k y x -- Left version of monadic hedgeUnionWithKey. -- (Monad is threaded left-to-right in tree) -- hedgeUnionWithKeyML :: (Ord k, Monad m) => (k -> a -> a -> m a) -> (k -> Ordering) -> (k -> Ordering) -> Map k a -> Map k a -> m (Map k a) hedgeUnionWithKeyML f cmplo cmphi t1 Tip = return t1 hedgeUnionWithKeyML f cmplo cmphi Tip (Bin _ kx x l r) = return $ join kx x (filterGt cmplo l) (filterLt cmphi r) hedgeUnionWithKeyML f cmplo cmphi (Bin _ kx x l r) t2 = do { newl <- hedgeUnionWithKeyML f cmplo cmpkx l lt ; newx <- case found of Nothing -> return x Just y -> f kx x y ; newr <- hedgeUnionWithKeyML f cmpkx cmphi r gt ; return $ join kx newx newl newr } where cmpkx k = compare kx k lt = trim cmplo cmpkx t2 (found,gt) = trimLookupLo kx cmphi t2 -- And some test cases: fm1 = fromList [(1,["a"]),(2,["b","c"]),(3,["d"])] fm2 = fromList [(1,["b","c"]),(4,["e"])] fm3 = fromList [(1,["d","e"]),(2,["c","d"]),(4,["f"])] -- Test function returns Nothing if list values have a member in common: comb ovs nvs | null (List.intersect ovs nvs) = Just (ovs++nvs) | otherwise = Nothing fm12 = Just $ fromList [(1,["a","b","c"]),(2,["b","c"]),(3,["d"]),(4,["e"])] fm13 = Nothing fm23 = Just $ fromList [(1,["b","c","d","e"]),(2,["c","d"]),(4,["e","f"])] fmt1 = unionWithM comb fm1 fm2 == fm12 fmt2 = unionWithM comb fm1 fm3 == fm13 fmt3 = unionWithM comb fm2 fm3 == fm23 -- Test function uses state to accumulate combined keys combk :: k -> [a] -> [a] -> State.State [k] [a] combk k ov nv = State.State (\s -> (ov++nv,s++[k])) fmk12 = ( fromList [(1,["a","b","c"]),(2,["b","c"]),(3,["d"]),(4,["e"])] , [1] ) fmk13 = (fromList [(1,["a","d","e"]),(2,["b","c","c","d"]),(3,["d"]),(4,["f"])] ,[1,2] ) fmk23 = (fromList [(1,["b","c","d","e"]),(2,["c","d"]),(4,["e","f"])] ,[1,4]) fmt4 = State.runState (unionWithKeyM combk fm1 fm2) [] == fmk12 fmt5 = State.runState (unionWithKeyM combk fm1 fm3) [] == fmk13 fmt6 = State.runState (unionWithKeyM combk fm2 fm3) [] == fmk23 fmtall = and [fmt1,fmt2,fmt3,fmt4,fmt5,fmt6] ]] ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Tue, 09 Nov 2004 15:22:53 +0000, Graham Klyne
At 13:06 09/11/04 +0000, Simon Marlow wrote:
On 09 November 2004 12:45, Graham Klyne wrote:
I'd like to propose an addition to the FiniteMap module in the form of a monadic version of plusFM_C. The proposed implementation is pretty much a copy of the existing implementation within a do block.
Data.FiniteMap will shortly be deprecated in favour of DData.Map (which will be renamed to Data.Map when it is imported). Perhaps you'd like to reformulate the proposal using Data.Map instead?
Proposed addition: [***]
Ok, but in order to have a consistent interface, we'll need monadic versions of a lot of functions: there are Set, IntMap, IntSet types, and intersection, difference, etc. Might be a lot of work. A solution may be to make standard versions a special case of the monadic ones, still I wonder about performance issues. Cheers, JP.

At 23:35 09/11/04 +0100, Jean-Philippe Bernardy wrote:
On Tue, 09 Nov 2004 15:22:53 +0000, Graham Klyne
wrote: At 13:06 09/11/04 +0000, Simon Marlow wrote:
On 09 November 2004 12:45, Graham Klyne wrote:
I'd like to propose an addition to the FiniteMap module in the form of a monadic version of plusFM_C. The proposed implementation is pretty much a copy of the existing implementation within a do block.
Data.FiniteMap will shortly be deprecated in favour of DData.Map (which will be renamed to Data.Map when it is imported). Perhaps you'd like to reformulate the proposal using Data.Map instead?
Proposed addition: [***]
Ok, but in order to have a consistent interface, we'll need monadic versions of a lot of functions: there are Set, IntMap, IntSet types, and intersection, difference, etc. Might be a lot of work. A solution may be to make standard versions a special case of the monadic ones, still I wonder about performance issues.
I hadn't thought about that specifically, but I did think about other similar functions on Map values, and it raises questions of both utility and consistency. My suggestion comes from a specific and real requirement in some software I'm writing. Because the actual type is abstract (hidden), I can't do it externally to the module, other than by using several function calls to extract, merge, delete and re-insert elements, which doesn't seem desirable. In this case, I decided to push for the particular function that I knew I wanted, and to not expend energy on other functions whose actual utility was uncertain. FWIW, other candidate functions for this treatment that I see would be: , insertWith, insertWithKey, insertLookupWithKey , differenceWith , differenceWithKey , intersectionWith , intersectionWithKey , fromListWith , fromListWithKey , fromAscListWith , fromAscListWithKey Hmmm, I also note: , mapAccum , mapAccumWithKey and wonder why these aren't done with a monadic function? It looks a bit like a state monad operation to me. #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Wed, 10 Nov 2004 10:42:58 +0000, Graham Klyne
I hadn't thought about that specifically, but I did think about other similar functions on Map values, and it raises questions of both utility and consistency.
My suggestion comes from a specific and real requirement in some software I'm writing. Because the actual type is abstract (hidden), I can't do it externally to the module, other than by using several function calls to extract, merge, delete and re-insert elements, which doesn't seem desirable.
In this case, I decided to push for the particular function that I knew I wanted, and to not expend energy on other functions whose actual utility was uncertain.
That is sensible, yet you should consider my point of view as maintainer. ;) I'd certainly welcome extension proposals, yet DData has gone through a stabilization process in order to include it into the standard hierachy. Therefore I find it unwise to make modifications to it right before it gets "into production". Cheers, JP.

At 13:32 13/11/04 +0100, Jean-Philippe Bernardy wrote:
On Wed, 10 Nov 2004 10:42:58 +0000, Graham Klyne
wrote: I hadn't thought about that specifically, but I did think about other similar functions on Map values, and it raises questions of both utility and consistency.
My suggestion comes from a specific and real requirement in some software I'm writing. Because the actual type is abstract (hidden), I can't do it externally to the module, other than by using several function calls to extract, merge, delete and re-insert elements, which doesn't seem desirable.
In this case, I decided to push for the particular function that I knew I wanted, and to not expend energy on other functions whose actual utility was uncertain.
That is sensible, yet you should consider my point of view as maintainer. ;) I'd certainly welcome extension proposals, yet DData has gone through a stabilization process in order to include it into the standard hierachy. Therefore I find it unwise to make modifications to it right before it gets "into production".
That's fair enough. Unfortunately, it leaves me little choice for my application than to use a forked version of the Map module (which I am now doing). This is unfortunate for me because I'm trying to create a stand-alone "literate Haskell" module that is easy to load and run in any Haskell environment; i.e. minimum external dependencies other than standard libraries. I did spend a little time thinking about if there could be a way to provide just enough access to the internals of Map (and friends) to allow the functionality to be extended by another module. But I did not have any great inspiration. (In thinking about this, I was reminded that traditional OO languages often have a feature that allows access to internals of data structures to derived class implementations, but not to other code; e.g. Java's 'protected' access. I'm not sure that thought is particularly relevant to Haskell, other than to illustrate a perceived need.) #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact
participants (3)
-
Graham Klyne
-
Graham Klyne
-
Jean-Philippe Bernardy