
Hello- Is there standard function in Haskell that effectively does an inverse scan? For example, scanl1 (\ x y -> x+y) [1,2,3,4] == [1,3,6,10]. So is there a very simple built-in way to do this hypothetical example?: unscanl1 (\ x y -> y-x) [1,3,6,10] == [1,2,3,4] Thanks, Jeffrey

I was able to build something incredibly convoluted that accomplishes what
you want, but I'm sure there's a better way to do it.
unscanl1 :: (a -> a -> a) -> [a] -> [a]
unscanl1 f xs = (head xs) : (map (\(a:b:_) -> f a b) $ convert xs)
where
convert = takeWhile (\xs -> length xs == 2) . map (take 2) . tails
I'm also not sure if this works in the general case, but it worked with the
example you gave and a couple other quick test cases I thought up. As with
any case where you use head, bad stuff will happen if feed an empty list,
so either add a case that matches on [] or make sure not to feed it an
empty list.
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Wed, Jan 11, 2012 at 23:44, Jeffrey Thornton
Hello-
Is there standard function in Haskell that effectively does an inverse scan? For example,
scanl1 (\ x y -> x+y) [1,2,3,4] == [1,3,6,10].
So is there a very simple built-in way to do this hypothetical example?:
unscanl1 (\ x y -> y-x) [1,3,6,10] == [1,2,3,4]
Thanks, Jeffrey _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

2012/1/12 Kyle Murphy
I was able to build something incredibly convoluted that accomplishes what you want, but I'm sure there's a better way to do it.
Not sure if it's a better way. unscan l = head l : zipWith (subtract) l (tail l) Corrected to work for empty lists : unscan [] = [] unscan l@(x:xs) = x : zipWith (subtract) l xs David.

2012/1/12 David Virebayre
2012/1/12 Kyle Murphy
: I was able to build something incredibly convoluted that accomplishes what you want, but I'm sure there's a better way to do it.
Not sure if it's a better way.
Disregard that reply, I overlooked the question. My only excuse is that it's early in the morning. that would be : unscan f l = if null l then [] else head l : zipWith f l (tail l) David. Where's my coffee ! Silly me. I don't drink coffee.

Direct recursion is almost always clearer if you are traversing the
list at a "different speed". The usual list functionals (map, filter,
folds) are all speed 1 - traversing one element at a time. Here we
want pairwise traversal:
unscan :: (a -> a -> b) -> [a] -> [b]
unscan f (a:b:bs) = f a b : unscan f b bs
unscan _ _ = []
On 12 January 2012 06:41, Kyle Murphy
I was able to build something incredibly convoluted that accomplishes what you want, but I'm sure there's a better way to do it.
...

Is "speed x" at least a somewhat universal term for the number of list
elements that get operated on per iteration? It works really well.
I was also wondering about what you just pointed out: if there's a nice way
to form (what I now know to call) speed >1 functions. Your form looks a lot
nicer than some of the stranger things I've been coming up with.
On Thu, Jan 12, 2012 at 1:37 AM, Stephen Tetley
Direct recursion is almost always clearer if you are traversing the list at a "different speed". The usual list functionals (map, filter, folds) are all speed 1 - traversing one element at a time. Here we want pairwise traversal:
unscan :: (a -> a -> b) -> [a] -> [b] unscan f (a:b:bs) = f a b : unscan f b bs unscan _ _ = []

Hi Jeffrey My version actually contains an error, it should be: unscan :: (a -> a -> b) -> [a] -> [b] unscan f (a:b:bs) = f a b : unscan f (b:bs) unscan _ _ = [] A slightly less concise, but optimized version avoids putting the second element back in a list: unscan f (a:b:bs) = f a b : go b bs where go _ [] = [] go x (z:zs) = f x z : go z zs unscan _ _ = [] The first mention of "speed" for traversing lists at different rates I've seen was in the paper "There and Back Again" by Olivier Danvy and Mayer Goldberg. http://www.brics.dk/RS/02/12/BRICS-RS-02-12.pdf Best wishes Stephen

Hello. Can I upload file using http-enumerator, hxt? What best way to take a html page from one server, maybe make some transformation of this html and upload it (transformed) to other server? I can use hxt to download file and to do some transformation. But how can I upload it to other server?

Generally you can download a file by using GET request and upload it with
POST request. See urlEncodedBody in http-enumerator:
http://hackage.haskell.org/packages/archive/http-enumerator/0.7.2.3/doc/html...
Best regards,
Krzysztof Skrzętnicki
2012/1/13 Никитин Лев
Hello.
Can I upload file using http-enumerator, hxt?
What best way to take a html page from one server, maybe make some transformation of this html and upload it (transformed) to other server?
I can use hxt to download file and to do some transformation. But how can I upload it to other server?
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am 13.01.2012 19:19, schrieb Stephen Tetley:
Hi Jeffrey
My version actually contains an error, it should be:
unscan :: (a -> a -> b) -> [a] -> [b] unscan f (a:b:bs) = f a b : unscan f (b:bs) unscan _ _ = []
A slightly less concise, but optimized version avoids putting the second element back in a list:
unscan f (a:b:bs) = f a b : go b bs where go _ [] = [] go x (z:zs) = f x z : go z zs unscan _ _ = []
This version contains duplicate code: The first line could be: unscan f (a : bs) = go a bs "putting the second element back" can be avoided by @-Patterns! unscan f (a : bs@(b : _)) = f a b : unscan bs Cheers Christian

Christian Maeder
Am 13.01.2012 19:19, schrieb Stephen Tetley:
unscan :: (a -> a -> b) -> [a] -> [b] unscan f (a:b:bs) = f a b : unscan f (b:bs) unscan _ _ = []
"putting the second element back" can be avoided by @-Patterns!
unscan f (a : bs@(b : _)) = f a b : unscan bs
And if Stephen or Christian had gone that little extra step to actually run their code they would find: unscan (flip (-)) [1,3,6,10] ===> [2,3,4] This is not what the OP asked for. (Because [1,3,6,10] is the result of scanl1 (+) [1,2,3,4]. Where did the 1 go?) The reason? The suffix-1 family of list combinators expect their list to contain at least one element, which they treat specially. So to unscanl1 we need to put the 'zeroeth' element back where scanl1 takes it from -- that is, on the front of the result. To follow the style in the Prelude: unscanl1 :: (a -> a -> a) -> [a] -> [a] unscanl1 _ [] = [] -- error-trap for empty lists unscanl1 f (x0: xs) = x0: unscanl f x0 xs -- zeroeth element on the front unscanl :: (a -> a -> b) -> a -> [a] -> [b] unscanl f x0 (x:xs) = f x0 x : unscanl f x xs unscanl _ _ _ = [] Then: unscanl1 (flip (-)) [1,3,6,10] ===> [1,2,3,4] (I think that style of definition is the clearest to understand. You could possibly avoid repeating 'x' using @-patterns or a helper function (go) or a sub-case (per the Prelude), but I doubt it would make much difference to efficiency.) AntC
participants (8)
-
AntC
-
Christian Maeder
-
David Virebayre
-
Jeffrey Thornton
-
Krzysztof Skrzętnicki
-
Kyle Murphy
-
Stephen Tetley
-
Никитин Лев