Proposal #1464: add dropPrefix to Data.List

Conor McBride ctm at cs.nott.ac.uk
Wed Jun 27 04:35:50 EDT 2007


Hi Ian

I think I have this thing lying around as well:

On 27 Jun 2007, at 02:26, Ian Lynagh wrote:

>     dropPrefix :: Eq a => [a] -> [a] -> Maybe [a]
>     dropPrefix [] ys = Just ys
>     dropPrefix (x:xs) (y:ys)
>      | x == y = dropPrefix xs ys
>     dropPrefix _ _ = Nothing

But while I was grepping for it, I found I had written something
slightly different. Recalling that Monoid w makes Applicative ((,) w),
I have

   leftFactor :: Eq x => [x] -> [x] -> ([x], ([x], [x]))
   leftFactor (x : xs)  (y : ys) | x == y  = ([x], ()) *> leftFactor  
xs ys
   leftFactor xs        ys                 = pure (xs, ys)

Properties:

   if leftFactor xs ys = (zs, (xs', ys'))
   then zs is the longest list such that
     xs == zs ++ xs'
     ys == zs ++ ys'

You get dropPrefix cheaply

   dropPrefix :: Eq a => [a] -> [a] -> Maybe [a]
   dropPrefix xs ys
     | (_, ([], zs)) <- leftFactor xs ys = Just zs
     | otherwise = Nothing

but I also use it to do "common ancestor" calculations on hierarchical
namespaces. Indeed, I have in the past used this thing on paths/contexts
to determine whether two subterms of a given term were nested or not.

A more frivolous usage is this variation on an ancient program:

   gcdList :: Eq x => [x] -> [x] -> Maybe [x]
   gcdList xs ys = case leftFactor xs ys of
     (_, ([], []))  -> Just xs
     (_, ([], zs))  -> gcdList xs zs
     (_, (zs, []))  -> gcdList zs ys
     _              -> Nothing

gcdList xs ys calculates the largest zs such that
   xs == [1..m] >> zs and ys == [1..n] >> zs
if any such exists.

I was wondering what solutions there might be to
   xs ++ ys == ys ++ xs
when out it popped! But I digress.

It could well be that dropPrefix is much the more common, and hence that
extra fuss required to get it from leftFactor isn't worth it, but I
thought I'd punt out the possibility.

As for whether these things should return in Maybe, or some arbitrary
MonadPlus m, well, that seems like one instance of a wider question. We
surely need a consistent policy here: do we target the specific  
*minimal*
notion of computation supporting whatever it is (in this case, failure),
or attempt to abstract an *arbitrary* such. If the latter, one  
should, of
course, ask if Monad is too specific...

Now I come to think about it, I quite like the minimal approach. It  
keeps
the individual operations as simple as possible, and it pulls out the
Maybe -> whatever homomorphism as a largest left factor. Or something.

All the best

Conor




More information about the Libraries mailing list