Sequence differences

I have a Scheme function that calculates sequence differences, i.e., it returns a sequence that is the difference between the 2nd and the 1st element, the 3rd and the 2nd, the 4th and the 3rd, etc. (define s (lambda (f l) (cond ((null? (cdr l)) '()) (else (cons (f (cadr l) (car l)) (s f (cdr l))))))) where (s - '(0,1,3,6,10,15,21,28)) => (1,2,3,4,5,6,7) I'm thinking the same function in Haskell would be something like s :: s f [] = [] s f [x] = [x] s f l = [ a f b | (a,b) <- zip (init l) (tail l)] but can't figure out what the function typing would be. Michael

So, we can walk through it-
s f [] = [] s f [x] = [x] s f l = [ a f b | (a,b) <- zip (init l) (tail l)]
First, we can write some of it to be a little more idiomatic, viz: s _ [] = [] s _ [x] = [x] s f ls = [f a b | (a,b) <- zip (init ls) (tail ls)] First, we have a function type, we can tell the variable f is a function because it's applied to arguments in the third case, since it's applied to two arguments, it's binary, so `s :: (a -> b -> c) -> ?` however, from the second case, we know that whatever the type of the second argument (a list of some type `a1`) is also the type of the return argument, since the `s` acts as the identity for lists of length less than 2, so s :: (a -> b -> a1) -> [a1] -> [a1] However, since the arguments for `f` are drawn from the same list, the argument types must _also_ be of type `a1`, leaving us with: s :: (a -> a -> a) -> [a] -> [a] This is, interestingly enough, precisely the type of foldr1. We can write your original function in another, cleaner way though, too, since zip will "zip" to the smaller of the two lengths, so you don't need to worry about doing the init and the tail, so `s` is really: s _ [] = [] s _ [x] = [x] s f ls = [f a b | (a,b) <- zip ls (tail ls)] but there is a function which does precisely what the third case does, called "zipWith" which takes a binary function and two lists and -- well -- does what that list comprehension does. In fact, it does what your whole function does... In fact, it _is_ your function, specialized a little, eg: yourZipWith f ls = zipWith f ls (tail ls) Hope that helps /Joe michael rice wrote:
I have a Scheme function that calculates sequence differences, i.e., it returns a sequence that is the difference between the 2nd and the 1st element, the 3rd and the 2nd, the 4th and the 3rd, etc.
(define s (lambda (f l) (cond ((null? (cdr l)) '()) (else (cons (f (cadr l) (car l)) (s f (cdr l)))))))
where
(s - '(0,1,3,6,10,15,21,28)) => (1,2,3,4,5,6,7)
I'm thinking the same function in Haskell would be something like
s :: s f [] = [] s f [x] = [x] s f l = [ a f b | (a,b) <- zip (init l) (tail l)]
but can't figure out what the function typing would be.
Michael
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Joe Fredette
We can write your original function in another, cleaner way though, too, since zip will "zip" to the smaller of the two lengths, so you don't need to worry about doing the init and the tail, so `s` is really:
s _ [] = [] s _ [x] = [x] s f ls = [f a b | (a,b) <- zip ls (tail ls)]
but there is a function which does precisely what the third case does, called "zipWith" which takes a binary function and two lists and -- well -- does what that list comprehension does. In fact, it does what your whole function does... In fact, it _is_ your function, specialized a little, eg:
yourZipWith f ls = zipWith f ls (tail ls)
A nice generalization of this that can be really useful is movingWindow :: Int -> [a] -> [[a]] movingWindow 1 xs = map (:[]) xs movingWindow n xs = zipWith (:) xs . tail $ movingWindow (n-1) xs So for example,
movingWindow 3 [1..10] [[1,2,3],[2,3,4],[3,4,5],[4,5,6],[5,6,7],[6,7,8],[7,8,9],[8,9,10]]
Then you can write diff :: (Num a) => [a] -> [a] diff = map (\[x,y] -> y - x) . movingWindow 2 Hopefully the intermediate lists are optimized away, but I haven't done any performance testing. Chad

On Fri, 10 Apr 2009, Chad Scherrer wrote:
A nice generalization of this that can be really useful is
movingWindow :: Int -> [a] -> [[a]] movingWindow 1 xs = map (:[]) xs movingWindow n xs = zipWith (:) xs . tail $ movingWindow (n-1) xs
So for example,
movingWindow 3 [1..10] [[1,2,3],[2,3,4],[3,4,5],[4,5,6],[5,6,7],[6,7,8],[7,8,9],[8,9,10]]
movingWindow n xs = take (length xs - n +1) $ map (take n) $ tails xs or more efficient using utility-ht package: movingWindow n xs = Data.List.Match.take (drop (n-1) xs) $ map (take n) $ tails xs
Then you can write
diff :: (Num a) => [a] -> [a] diff = map (\[x,y] -> y - x) . movingWindow 2
Hopefully the intermediate lists are optimized away, but I haven't done any performance testing.
I'm not sure. You are safer and more efficient when you restrict to pairs. Since I often need the function, I defined: http://hackage.haskell.org/packages/archive/utility-ht/0.0.4/doc/html/Data-L... Then diff = mapAdjacent subtract

henning thielmann writes:
movingWindow n xs = take (length xs - n +1) $ map (take n) $ tails xs
or more efficient using utility-ht package:
movingWindow n xs = Data.List.Match.take (drop (n-1) xs) $ map (take n) $ tails xs
Oh, very nice. I was a little frustrated writing the recursion explicitly. I guess you could also write movingWindow n xs = zipWith const (map (take n) $ tails xs) $ drop (n-1) xs Hmm, maybe this is obvious, if Data.List.Match.take == zipWith (flip const) (I've never used it)
I'm not sure. You are safer and more efficient when you restrict to pairs. Since I often need the function, I defined:
http://hackage.haskell.org/packages/archive/utility-ht/0.0.4/d oc/html/Data-List-HT.html#v%3AmapAdjacent
Then diff = mapAdjacent subtract
Yes, I agree if you know you'll be using a binary operator, and not a more general n-ary function. Chad
participants (5)
-
Chad Scherrer
-
Henning Thielemann
-
Joe Fredette
-
michael rice
-
Scherrer, Chad