Does somebody know about these functions?

Two functions that I see useful are described here and I would like to know if they are defined in some more or less standard Haskell library. Hoogle (http://www.haskell.org/hoogle) did not reveal anything about that. Function 'inter' applies given function to each succeeding pair of elements of a list. inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l) Example usage: and $ inter (<=) l -- checks if 'l' is ordered inter (,) l -- gives succeeding pairs Function 'withPair' takes a pair and applies a function to it's first element, another function to it's second element and finally combines the results with yet another function. withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c withPair f fa fb (a,b) = fa a `f` fb b Example usage: words [] = [] words s = withPair (:) id words (break isSpace $ dropWhile isSpace s) lines [] = [] lines s = withPair (:) id lines (break (== '\n') s) mapPair = withPair (,) This function can abstract away the (in my opinion ugly) pattern (as seen in the examples): foo list = let (a,b) = <somefun> list in <somefun2> a `<combinedWith>` foo b Anyone knows about these two functions or variants thereof? Cheers /Johan

On Tue, Feb 28, 2012 at 06:06:25PM +0100, Johan Holmquist wrote:
inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l)
I've never seen this function defined anywhere, but it looks nice.
withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c withPair f fa fb (a,b) = fa a `f` fb b
Note that withPair f g h === uncurry f . (g *** h) although using withPair is probably nicer (it certainly involves fewer parentheses). -Brent

On 2/28/12 1:25 PM, Brent Yorgey wrote:
On Tue, Feb 28, 2012 at 06:06:25PM +0100, Johan Holmquist wrote:
inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l)
I've never seen this function defined anywhere, but it looks nice.
I've used it a few times, but never seen it defined in libraries. Of course, you can simplify the implementation by: inter f xs = zipWith f xs (tail xs)
withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c withPair f fa fb (a,b) = fa a `f` fb b
Note that
withPair f g h === uncurry f . (g *** h)
Also: import Data.Function.Pointless -- from pointless-fun withPair f g h = uncurry (f $:: g ~> h ~> id) which is certainly no shorter since pointless-fun doesn't handle tuples directly like the arrow combinators do, but it does generalize much further. Though I can't say as I've used the withPair idiom very often, despite using (***) and friends quite regularly... -- Live well, ~wren

On 01/03/12 14:40, wren ng thornton wrote:
Of course, you can simplify the implementation by:
inter f xs = zipWith f xs (tail xs) inter f = zipWith f <*> tail
-- Tony Morris http://tmorris.net/

So, these two functions do not appear to be defined, perhaps because many of their potential uses could be expressed using the functions from Data.Applicative and Data.Arrow instead. You may have noticed that the words and lines examples where defunct, but not difficult to fix: words = go . dropWhile isSpace where go [] = [] go s = withPair (:) id words (break isSpace s) lines [] = [] lines s = withPair (:) id (lines . safeTail) (break (== '\n') s) safeTail [] = [] safeTail l = tail l Ofcourse RHS of 'lines s' can be written (and likewise for words): uncurry (:) $ second (lines . safeTail) $ break (== '\n') s which looks rather nice to me. /Johan

Am 28.02.2012 um 18:06 schrieb Johan Holmquist:
Two functions that I see useful are described here and I would like to know if they are defined in some more or less standard Haskell library. Hoogle (http://www.haskell.org/hoogle) did not reveal anything about that.
Function 'inter' applies given function to each succeeding pair of elements of a list.
inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l)
This is the same as inter :: (a -> a -> b) -> [a] -> [b] inter f l = zipWith f l (tail l) and you can use it to define the good old Fibonacci sequence: fibs = 0 : 1 : inter (+) fibs

inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l)
This is the same as
inter :: (a -> a -> b) -> [a] -> [b] inter f l = zipWith f l (tail l)
Except when l == [], but the second equation can be replaced by this nicer one.
and you can use it to define the good old Fibonacci sequence:
fibs = 0 : 1 : inter (+) fibs
Another use :-) (sorry Holger for duplicate -- hit wrong answer button at first) Together, these functions can be used to define a variant of groupBy that does the "expected thing" in the case of groupBy (<) for example. groupBy f l = gby $ zip (undefined : inter f l) l where gby [] = [] gby ((_,x):ps) = withPair (:) ((x:) . map snd) gby (span fst ps)
groupBy (<) [1,2,3, 2,3, 1,2] [[1,2,3],[2,3],[1,2]]
/Johan

Am 28.02.2012 um 20:21 schrieb Johan Holmquist:
inter :: (a -> a -> b) -> [a] -> [b] inter f [] = [] inter f l = map (uncurry f) $ zip l (tail l)
This is the same as
inter :: (a -> a -> b) -> [a] -> [b] inter f l = zipWith f l (tail l)
Except when l == [], but the second equation can be replaced by this nicer one.
Even then. :) (zipWith f l (tail l)) first tries to match l with pattern (a:as), and if that fails it will not touch its other argument (tail l).

Except when l == [], but the second equation can be replaced by this nicer one.
Even then. :) (zipWith f l (tail l)) first tries to match l with pattern (a:as), and if that fails it will not touch its other argument (tail l).
Hm, you're right, it did work for empty lists. I wonder if one dare trust it to always be so. /Johan

On 28 February 2012 17:06, Johan Holmquist
Function 'withPair' takes a pair and applies a function to it's first element, another function to it's second element and finally combines the results with yet another function.
withPair :: (a' -> b' -> c) -> (a -> a') -> (b -> b') -> (a,b) -> c withPair f fa fb (a,b) = fa a `f` fb b
withPair is the Dovekie function from combinatory logic but with a pair for the non-combinator arguments (a,b) and the arg order changed to be more convenient to program with. There was a thread about inter[*] on the beginners list last month http://www.haskell.org/pipermail/beginners/2012-January/009329.html [*] or an inter-like function depending how you want to treat the initial value. I made a mistake with my suggestion.
participants (6)
-
Brent Yorgey
-
Holger Siegel
-
Johan Holmquist
-
Stephen Tetley
-
Tony Morris
-
wren ng thornton