
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