#5894: Add generalization of Data.Map.unionWith with (a -> b -> c) as the
combining function
------------------------------+---------------------------------------------
 Reporter:  joeyadams         |          Owner:                   
     Type:  feature request   |         Status:  new              
 Priority:  normal            |      Component:  libraries (other)
  Version:  7.4.1             |       Keywords:                   
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple 
  Failure:  None/Unknown      |       Testcase:                   
Blockedby:                    |       Blocking:                   
  Related:                    |  
------------------------------+---------------------------------------------
 The signature of
 [http://hackage.haskell.org/packages/archive/containers/latest/doc/html
 /Data-Map.html#v:unionWith Data.Map.unionWith] is:

 {{{
 unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
 }}}

 [http://hackage.haskell.org/packages/archive/containers/latest/doc/html
 /Data-Map.html#v:intersectionWith intersectionWith], on the other hand,
 has a more general signature:

 {{{
 intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k
 c
 }}}

 The reason the combining function in {{{unionWith}}} is constrained to
 {{{(a -> a -> a)}}} is because of the possibility of values in one map not
 present in the other.  {{{unionWith}}} only applies the combining function
 for values present in both maps; it uses existing values for the rest.

 I'd like to be able to write this function:

 {{{
 -- | Combine two maps.  Substitute 'Nothing' for any value present in only
 one
 -- of the maps.
 unionMaybes :: Ord k => Map k a -> Map k b -> Map k (Maybe a, Maybe b)
 }}}

 However, it's awkward with {{{unionWith}}}:

 {{{
 unionMaybes left right =
         Map.unionWith combine (Map.map mkLeft left) (Map.map mkRight
 right)
     where
         mkLeft   l = (Just l, Nothing)
         mkRight  r = (Nothing, Just r)
         combine (Just l, Nothing) (Nothing, Just r) = (Just l, Just r)
         combine _ _ = error "Shouldn't happen"
 }}}

 It'd be nicer to have a generalization of {{{unionWith}}} that can
 transform values only present in one of the maps.  Here is such a
 function, implemented in terms of {{{unionWith}}}:

 {{{
 -- | Like 'Map.unionWith', but apply a function even when a key is present
 in
 -- only one of the maps.
 --
 -- @'Map.unionWith' = 'combine' 'id' 'id'@
 combine :: Ord k
         => (a -> c)         -- ^ For keys only present in the left map
         -> (b -> c)         -- ^ For keys only present in the right map
         -> (a -> b -> c)    -- ^ For keys present in both maps
         -> Map k a          -- ^ Left map
         -> Map k b          -- ^ Right map
         -> Map k c
 combine onLeft onRight onBoth left right =
         Map.map apply $
         Map.unionWith combine_ (Map.map LeftOnly left) (Map.map RightOnly
 right)
     where
         combine_ (LeftOnly l) (RightOnly r) = LeftRight l r
         combine_ _ _ =
             error "combine: internal error (Data.Map.unionWith is not
 combining values correctly)"

         apply (LeftOnly l)    = onLeft l
         apply (RightOnly r)   = onRight r
         apply (LeftRight l r) = onBoth l r

 data Combine l r = LeftOnly l
                  | RightOnly r
                  | LeftRight l r
 }}}

 This way, {{{unionMaybes}}} can be written as:

 {{{
 unionMaybes :: Ord k => Map k a -> Map k b -> Map k (Maybe a, Maybe b)
 unionMaybes = combine (\l   -> (Just l,  Nothing))
                       (\r   -> (Nothing, Just r))
                       (\l r -> (Just l,  Just r))
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5894>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to