Ok, here is an attempt. I don't have time to explain, but it's not Myer's algorithm.
Try for example diff "abcabba" "cbabac" Gertjan Kamsteeg ================================ data In a = F a | S a | B a diff xs ys = steps ([(0,0,[],xs,ys)],[]) where steps (((_,_,ws,[],[]):_),_) = reverse ws steps d = steps (step d) where step (ps,qs) = let (us,vs) = h1 ps in (h3 qs (h2 us),vs) where h1 [] = ([],[]) h1 (p:ps) = let (rs,ss) = next p; (us,vs) = h1 ps in (rs++us,ss++vs) where next (k,n,ws,(x:xs),[]) = ([(k+1,n+1,F x:ws,xs,[])],[]) next (k,n,ws,[],(y:ys)) = ([(k-1,n+1,S y:ws,[],ys)],[]) next (k,n,ws,xs@(x:us),ys@(y:vs)) | x == y = ([],[(k,n+1,B x:ws,us,vs)]) | otherwise = ([(k+1,n+1,F x:ws,us,ys),(k-1,n+1,S y:ws,xs,vs)],[]) h2 [] = [] h2 ps@[_] = ps h2 (p@(k1,n1,_,_,_):ps@(q@(k2,n2,_,_,_):us)) | k1 == k2 = if n1 <= n2 then p:h2 us else q:h2 us | otherwise = p:h2 ps h3 ps [] = ps h3 [] qs = qs h3 (ps@(p@(k1,n1,_,_,_):us)) (qs@(q@(k2,n2,_,_,_):vs)) | k1 > k2 = p:h3 us qs | k1 == k2 = if n1 <= n2 then p:h3 us vs else q:h3 us vs | otherwise = q:h3 ps vs ----- Original Message ----- From: "George Russell" <[EMAIL PROTECTED]> To: <[EMAIL PROTECTED]> Sent: Thursday, November 21, 2002 6:39 PM Subject: diff in Haskell: clarification > Since various people seem to have misunderstood the problem, I shall try to state it > more precisely. > > > What is required is a function > > diff :: Ord a -> [a] -> [a] -> [DiffElement a] > > for the type > data DiffElement a = > InBoth a > | InFirst a > | InSecond a > > such that given the functions > > f1 (InBoth a) = Just a > f1 (InFirst a) = Just a > f1 (InSecond a) = Nothing > > and > > f2 (InBoth a) = Just a > f2 (InFirst a) = Nothing > f2 (InSecond a) = Just a > > the following identities hold: > > mapPartial f1 (diff l1 l2) == l1 > and > mapPartial f2 (diff l1 l2) == l2 > > This is a well-known problem. The most helpful Web page I could find about it is here: > > http://apinkin.net/space/DifferenceEngine > > There is an algorithm known as Myer's algorithm, but obviously I want it in Haskell > rather than C, and it would be nice if someone else had written it so I don't have to. > _______________________________________________ > Haskell mailing list > [EMAIL PROTECTED] > http://www.haskell.org/mailman/listinfo/haskell > _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell