Library function for map+append

Hello all, During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp: mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency? Of course, (map f list) ++ append would do the same as mapapp f list append but with less efficiency. Or am I wrong? Thanks Dusan

Hi.
Have you done any measurements that prove that such a function would
indeed increase performance noticeably?
2009/8/18 Dusan Kolar
Hello all,
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
Of course, (map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
Thanks
Dusan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Dusan Kolar
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
What does mapapp do? What is its type? At first I thought maybe you were rewriting concatMap, but now I can't tell what you're doing. http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-List.htm l#v%3AconcatMap Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
What does mapapp do? What is its type?
Never mind, I've got it now. Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

Dlists maybe good it all the app is written using them. Probably not good idea to switch to them in the middle of project... I know it is lazy, but I don't think it is able to eliminate operations, is it? At least intuitively, the map f list takes n*C ticks (C is for application of f and list "creation", n is the list length, f is of no importance, it is always the same, but list probably must be created due to ++). Then, (++) take n*K ticks (K for list creation - I want to write out the list at the end, so that it is created). In my case (mapapp), it is n*CK, where CK stands for f and list creation... the CK is very similar to C... Thus, I should save the n*K, or at least its large portion... shouldn't I? If not, how the compiler can eliminate the operations? Dusan Bulat Ziganshin wrote:
Hello Dusan,
Tuesday, August 18, 2009, 2:50:38 PM, you wrote:
but with less efficiency. Or am I wrong?
probably wrong. haskell is lazy language
also there is differential lists (dlist) implementation on hackage

Dusan Kolar
Dlists maybe good it all the app is written using them. Probably not good idea to switch to them in the middle of project...
I know it is lazy, but I don't think it is able to eliminate operations, is it?
At least intuitively, the map f list takes n*C ticks (C is for application of f and list "creation", n is the list length, f is of no importance, it is always the same, but list probably must be created due to ++).
Then, (++) take n*K ticks (K for list creation - I want to write out the list at the end, so that it is created).
In my case (mapapp), it is n*CK, where CK stands for f and list creation... the CK is very similar to C... Thus, I should save the n*K, or at least its large portion... shouldn't I? If not, how the compiler can eliminate the operations? IMHO, the best way to reason about functional programs is via equational reasoning. So let's consider straightforward definitions for map and (++):
map f [] = [] map f (x:xs) = f x : map f xs (++) [] l = l (++) (x:xs) l = x : (xs ++ l) Now let's see what happens with (map f x) ++ y doing case analysis and simplification with the above equations: (map f []) ++ y = [] ++ y = y (map f (x:xs)) ++ y = (f x : map f xs) ++ y = f x : (map f xs ++ y) So: (map f []) ++ y = y (map f (x : xs)) ++ y = f x : (map f xs ++ y) Now consider trivial definition for mapapp: mapapp f x y = (map f x) ++ y. Substituting this backwards into the above equations, we get: mapapp f [] y = y mapapp f (x : xs) y = f x : (mapapp f x xs) which is exactly the definition you've listed. Of course, a Haskell implementation is not *required* to do such transformations, but unless you really observe the difference in performance, it's more or less safe to assume there would be no intermediate list creation/destruction. -- S. Y. A(R). A.

2009/8/18 Dusan Kolar
Dlists maybe good it all the app is written using them. Probably not good idea to switch to them in the middle of project...
I have a different criterion for DLists. I think they are best to use in small scopes (I think the same of monads), as opposed to interfacing between different parts of a project. A DList is well-suited when you are *outputting* a list using appends; i.e. just concatenating stuff together, but not looking at the heads or iterating over the lists. The DList Quicksort is a perfect example. It also makes a good monoid for Writer. toList it after you're done generating; this is an efficient operation. Luke

Dusan Kolar wrote:
Hello all,
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
Of course, (map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
Thanks
Dusan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
mapapp = ((++) .) . map Reasoning about efficiency in a pure lazy language is different. -- Tony Morris http://tmorris.net/

2009/8/18 Dusan Kolar
Hello all,
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
Can't think of something like that either but at least we can make it shorter and less readable ;) mapapp f xs tail = foldr ((:) . f) tail xs
Of course, (map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
Yes, that is less efficient because ++ has to create N new cons cells if "list" has length N. -- Fruhwirth Clemens http://clemens.endorphin.org

Clemens Fruhwirth
2009/8/18 Dusan Kolar
: Hello all,
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
Can't think of something like that either but at least we can make it shorter and less readable ;)
mapapp f xs tail = foldr ((:) . f) tail xs
Of course, (map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
Yes, that is less efficient because ++ has to create N new cons cells if "list" has length N. No, it does not *have to*.
Fruhwirth Clemens http://clemens.endorphin.org _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- S. Y. A(R). A.

module Main where mymap f xs = m xs where m [] = [] m (x:xs) = f x:m xs mymapp1 f xs ys = m xs where m [] = ys m (x:xs) = f x:m xs mymapp2 f [] ys = ys mymapp2 f (x:xs) ys = f x:mymapp2 f xs ys mapp1 f xs ys = (f`map`xs) ++ ys mapp2 f xs ys = (f`mymap`xs) ++ ys mapp3 f xs ys = mymapp1 f xs ys mapp4 f xs ys = mymapp2 f xs ys mapp = mapp1 main = putStrLn . show . length $ mapp (+1) [1..100000000] [1,2,3] mapp1: 3.764s mapp2: 5.753s mapp3: 4.302s mapp4: 4.767s So, the fastest way is the simplest one. 18 августа 2009 г. 17:12 пользователь Artem V. Andreev (artem@aa5779.spb.edu) написал:
Clemens Fruhwirth
writes: 2009/8/18 Dusan Kolar
: Hello all,
During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
I tried hoogle to find such a function with no success. Is there any function/functions built-in "standard" libraries that could easily satisfy the functionality with the same or even better (?) efficiency?
Can't think of something like that either but at least we can make it shorter and less readable ;)
mapapp f xs tail = foldr ((:) . f) tail xs
Of course, (map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
Yes, that is less efficient because ++ has to create N new cons cells if "list" has length N. No, it does not *have to*.
Fruhwirth Clemens http://clemens.endorphin.org _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
--
S. Y. A(R). A. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

During a small project I'm trying to develop a small application. It becomes quite often that I need a function mapapp:
mapapp _ [] ap = ap mapapp f (a:as) ap = f a : map f as ap
Of course,
(map f list) ++ append would do the same as
mapapp f list append
but with less efficiency. Or am I wrong?
I timed each of the following five operations with ...
ghc -O2 --make MapApp.hs time ./MapApp
... and they produced no statistically significant differences. Each ran for about 3.8 seconds. Perhaps you can try it to convince yourself? Sean -- module Main where mapapp0 :: (a -> b) -> [b] -> [a] -> [b] mapapp0 f tail xs = map f xs ++ tail mapapp1 :: (a -> b) -> [b] -> [a] -> [b] mapapp1 _ tail [] = tail mapapp1 f tail (a:as) = f a : mapapp1 f tail as mapapp2 :: (a -> b) -> [b] -> [a] -> [b] mapapp2 f tail = go where go [] = tail go (x:xs) = f x : go xs mapapp3 :: (a -> b) -> [b] -> [a] -> [b] mapapp3 f tail = foldr ((:) . f) tail main = do writeFile "/dev/null" $ show $ [1 .. 10001000] -- writeFile "/dev/null" $ show $ mapapp0 (+3) [1 .. 10000000] [1 .. 1000] -- writeFile "/dev/null" $ show $ mapapp1 (+3) [1 .. 10000000] [1 .. 1000] -- writeFile "/dev/null" $ show $ mapapp2 (+3) [1 .. 10000000] [1 .. 1000] -- writeFile "/dev/null" $ show $ mapapp3 (+3) [1 .. 10000000] [1 .. 1000] return ()

Hello Sean, Tuesday, August 18, 2009, 7:49:21 PM, you wrote:
writeFile "/dev/null" $ show $ [1 .. 10001000]
it may be dominated by show+writeFile. i suggest you to compute, say, sum of all elements instead -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Tue, Aug 18, 2009 at 18:23, Bulat Ziganshin wrote:
Hello Sean,
Tuesday, August 18, 2009, 7:49:21 PM, you wrote:
writeFile "/dev/null" $ show $ [1 .. 10001000]
it may be dominated by show+writeFile. i suggest you to compute, say, sum of all elements instead
Thank you, Bulat. The results now show some variation. Sean -- writeFile "/dev/null" $ show $ sum $ [1 .. 10001000] 0m1.652s 0m1.634s 0m1.658s writeFile "/dev/null" $ show $ sum $ mapapp0 (+3) [1 .. 10000000] [1 .. 1000] 0m1.601s 0m1.613s 0m1.615s writeFile "/dev/null" $ show $ sum $ mapapp1 (+3) [1 .. 10000000] [1 .. 1000] 0m1.647s 0m1.656s 0m1.654s writeFile "/dev/null" $ show $ sum $ mapapp2 (+3) [1 .. 10000000] [1 .. 1000] 0m1.640s 0m1.645s 0m1.664s writeFile "/dev/null" $ show $ sum $ mapapp3 (+3) [1 .. 10000000] [1 .. 1000] 0m1.541s 0m1.531s 0m1.561s
participants (9)
-
Artem V. Andreev
-
Bayley, Alistair
-
Bulat Ziganshin
-
Clemens Fruhwirth
-
Dusan Kolar
-
Eugene Kirpichov
-
Luke Palmer
-
Sean Leather
-
Tony Morris