Generic tries (long)

apfelmus apfelmus at quantentunnel.de
Wed Jun 25 04:09:33 EDT 2008


Adrian Hey wrote:
> The type of the proposed merge now seems similarly strange to me..
> 
> merge :: (k -> Maybe a -> Maybe b -> Maybe c) -> map a -> map b -> map c
> 
> This requres users to define a function argument that is presumably of
> form
> 
> f k Nothing  Nothing  = undefined
> f k (Just a) Nothing  = fa  k a
> f k (Just a) (Just b) = fab k a b
> f k Nothing  (Just b) = fb  k b
> 
> Why not just pass fa,fab and fb directly, which will be more convenient
> for both users and implementors I think..
> 
> merge :: (k -> a ->      Maybe c) ->
>          (k -> a -> b -> Maybe c) ->
>          (k ->      b -> Maybe c) ->
>          map a -> map b -> map c

While every such f must have this form, in the sense that

   \f k -> (\a   -> f k (Just a) Nothing ,
            \a b -> f k (Just a) (Just b),
            \b   -> f k Nothing  (Just b))

is an isomorphism, it doesn't mean that it's explicitly implemented that 
way. The intention was that the library exports ready-made functions

   union, intersect, difference :: k -> Maybe a -> Maybe a -> Maybe a

and combinators like

   unionWith :: (k -> a -> b -> c)
             -> (k -> Maybe a -> Maybe b -> Maybe c)

that can be plugged into  merge , like

   merge intersect
   merge (unionWith $ curry snd)

Thus, the user doesn't implement the argument to  merge  himself unless 
he requires custom behavior. Hence, using one argument instead of three 
is more convenient here. The particular form

   union, intersect, difference :: Maybe a -> Maybe a -> Maybe a

has mnemonic value as well, since  Maybe a  is the finite map with one 
element, so the combinator  intersect  actually intersects two finite maps.


You're probably right concerning the efficiency of  merge . The problem 
is that  merge  may decide per element whether to intersect, union, 
difference or something, while the original  intersect  may only 
intersect elements and can hence throw whole subtrees away without 
looking into them.

An signature for  merge  that does not allow per-element tests would be

   merge :: (Bool -> Bool -> Bool) -> (k -> a -> b -> c)
         -> map a -> map b -> map c

Here, the boolean function determines membership while the second 
argument determines how to merge two values.

There is the small problem that the boolean function f ought to fulfill 
  f False False = False. This can be guaranteed by using a rank-2 type

   merge :: (forall a. Maybe a -> Maybe a -> Maybe a) -> ...

Incidentally, this restores the fact that the first argument combines 
one-element finite maps.


Regards,
apfelmus



More information about the Libraries mailing list