[Haskell-beginners] I have created an ugly Haskell program..
Michael Mossey
mpm at alumni.caltech.edu
Mon Nov 2 05:22:09 EST 2009
Function you seek is 'specialZip' below. 'fluff' and 'decapitate' are
helpers. Not extensively tested.
-- Given a list of ints that "should" all have values, fill in missing
-- values using the "last" value as default.
fluff :: String -> [Int] -> [(Int,String)] -> [(Int,String)]
fluff last (i:is) pss@((t,s):ps)
| i == t = (i,s) : fluff s is ps
| i < t = (i,last) : fluff last is pss
fluff last is [] = zip is (repeat last)
-- Given two lists, remove enough from the front to get to two equal keys.
decapitate [] _ = ([],[])
decapitate _ [] = ([],[])
decapitate xss@((tx,_):xs) yss@((ty,_):ys)
| tx < ty = decapitate xs yss
| ty < tx = decapitate xss ys
| ty == tx = (xss,yss)
specialZip d1 d2 =
let (dd1,dd2) = decapitate d1 d2
-- build set of every key that should be in final list
s = S.toAscList . S.fromList $ (map fst dd1) ++ (map fst dd2)
in case (dd1,dd2) of
([],[]) -> []
(xs1,xs2) ->
let f1 = fluff "" s xs1 -- use this set to fluff
f2 = fluff "" s xs2 -- each list
-- so final answer can be a simple zipWith
in zipWith (\(t1,s1) (t2,s2) -> (t1,(s1,s2))) f1 f2
Philip Scott wrote:
> .. and I am positive there must be a way of beautifying it, but I am
> struggling. I bet there is just some lovely way of making this all shrink to
> three lines..
>
> So here's the problem. I have two lists of tuples: (timestamp, value)
>
> What I would like to do in do a kind of 'zip' on two of these lists to make a
> list of (timestamp, (value1, value2)) with the following rules:
>
> - If the timestamps are equal it's easy - make your new element an move on
> - If one of the lists has a timestamp that the other doesn't, repeat an old
> value from the other list
> - If we don't have an old value yet, then don't create an element in the new
> list.
>
> e.g. if I ran my algorithm on these two lists
>
> d1 = [ (1,"a"), (2,"b"), (3,"c") ]
> d2 = [ (2,"b'"), (4,"d'") ]
>
> I would like to get
>
> result = [ (2, (b,b')), (3, (c,b')), (4, (c,d')) ]
>
> e.g. there was no data in d2 for our first element so we skipped it.
>
> Okay, so here is my code.. It works, but makes me feel a bit dirty. To explain
> my nomenclature 't' is 'timestamp of', 'v' is 'value of'. vx' and vy' are the
> 'old' values from the previous iteration in case a repeat is needed. They are
> Maybes because at the beginning there may be no old value.
>
> d1 = [ (1,"a"), (2,"b"), (3,"c") ]
> d2 = [ (2,"b'"), (4,"d'") ]
>
> t (x,y) = x
> v (x,y) = y
>
> js vx' vy' (x:xs) (y:ys)
> | t x == t y = ( (t x), (v x, v y) ) : js (Just (v x)) (Just (v y)) xs ys
> | t x < t y =
> maybe (js (Just (v x)) Nothing xs (y:ys))
> (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs (y:ys)))
> vy'
> | t x > t y =
> maybe (js Nothing (Just (v y)) (x:xs) ys)
> (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y)) (x:xs) ys))
> vx'
> js vx' vy' (x:xs) [] =
> maybe []
> (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs []))
> vy'
> js vx' vy' [] (y:ys) =
> maybe []
> (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y)) [] ys ))
> vx'
> js _ _ [] [] = []
>
> You call it with the first two arguments as Nothing to kick it off (I have a
> trivial wrapper function to do this)
>
> It works fine:
>
>> :t js
> js
> :: (Ord t) =>
> Maybe a1 -> Maybe a -> [(t, a1)] -> [(t, a)] -> [(t, (a1, a))]
>
>> js Nothing Nothing d1 d2
> [(2,("b","b'")),(3,("c","b'")),(4,("c","d'"))]
>
> But it just feels gross. Any advice on how to tame this beast would be greatly
> appreciated :)
>
> All the best,
>
> Philip
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list