Re: avoiding cost of (++)

2003-01-17 Thread Christian Sievers
Hal Daume III asked:

> > mapWithout :: ([a] -> b) -> [a] -> [b]
> > mapWithout f = mapWith' []
> > where mapWith' pre [] = []
> >   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
> 
> Unfortunately, this is very slow, due to the overhead of (++).
> 
> Any way I could speed this up would be great.  Note that order doesn't
> matter to 'f', but I do need that the order in which the elements of the
> list are processed be the same as in map.

If f is associative, i.e.  f (l1++l2) == f [f l1, f l2]
(this forces a=b), you can do

mapWithout :: ([a] -> a) -> [a] -> [a]
mapWithout f l = let n  = f [] -- neutral element
 b x y = f [x,y]   -- binary version
 sl = scanl b n l
 sr = scanr b n l
 in zipWith b sl (tail sr)

You'll probably rather use
mapWithout' (a->a->a) -> a -> [a] -> [a]
mapWithout'  bin_op   neutral  l = ...

If f is not defined for empty lists, you can combine (with a bit more work)
the results of scanl1 and scanr1.


HTH
Christian Sievers
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-17 Thread John van Groningen

Hal Daume III wrote:

>I have a function which behaves like map, except instead of applying the
>given function to, say, the element at position 5, it applies it to the
>entire list *without* the element at position 5.  An implementation looks
>like:
>
>> mapWithout :: ([a] -> b) -> [a] -> [b]
>> mapWithout f = mapWith' []
>> where mapWith' pre [] = []
>>   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
>
>Unfortunately, this is very slow, due to the overhead of (++).
>
>Any way I could speed this up would be great.  Note that order doesn't
>matter to 'f', but I do need that the order in which the elements of the
>list are processed be the same as in map.

The following version is probably faster:

mapWithout f [] = []
mapWithout f l = map_without l [] []
where
   map_without [e] t t2
= f t:t2
   map_without [e1,e2] t t2
= f (e2:t):f (e1:t):t2
   map_without l t t2
= map_without l1 (l2++t) (map_without l2 (l1++t) t2)
where
 (l1,l2) = splitAt (length l `div` 2) l

Regards,

John van Groningen


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: avoiding cost of (++)

2003-01-17 Thread Gerhard Navratil
If we can remove the effect of a single element we can reduce the number
of reductions significantly:

mapWithout2 :: ([a] -> a) -> ((a,a) -> a) -> [a] -> [a]
mapWithout2 f1 f2 l = map f2 list
  where list = zip (replicate (length l) (f1 l)) l

I only made the simplification the have a single data type so I could
use the following example for testing:

mw2 = mapWithout2 sum (uncurry (-)) (take 100 [1..])

Of course the code can be optimized but I usually do not care about
performnance issues ...

Gerhard


Gerhard Navratil
Teaching- And Research-Assistant

Vienna University of Technology, Austria
Institute for Geoinformation

Gusshausstr. 27-29
1040 Vienna

Tel.: ++43 (0) 1 / 58 801 - 12721
Fax.: ++43 (0) 1 / 58 801 - 12799
Cel.: ++43 (0) 699 / 197 44 761
http://www.geoinfo.tuwien.ac.at


-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]] On
Behalf Of Hal Daume III
Sent: Donnerstag, 16. Jänner 2003 17:11
To: Haskell Mailing List
Subject: avoiding cost of (++)


I have a function which behaves like map, except instead of applying the
given function to, say, the element at position 5, it applies it to the
entire list *without* the element at position 5.  An implementation
looks
like:

> mapWithout :: ([a] -> b) -> [a] -> [b]
> mapWithout f = mapWith' []
> where mapWith' pre [] = []
>   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs

Unfortunately, this is very slow, due to the overhead of (++).

Any way I could speed this up would be great.  Note that order doesn't
matter to 'f', but I do need that the order in which the elements of the
list are processed be the same as in map.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume


___
Haskell mailing list
[EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-17 Thread John Hughes
On Thu, 16 Jan 2003, Hal Daume III wrote:

> I have a function which behaves like map, except instead of applying the
> given function to, say, the element at position 5, it applies it to the
> entire list *without* the element at position 5.  An implementation looks
> like:
>
> > mapWithout :: ([a] -> b) -> [a] -> [b]
> > mapWithout f = mapWith' []
> > where mapWith' pre [] = []
> >   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
>
> Unfortunately, this is very slow, due to the overhead of (++).
>

I don't think this can be sped up appreciably without avoiding the
construction of the lists pre++xs. To accomplish that, I would change the
type of mapWithout, as follows:

mapPrePost :: ([a] -> [a] -> b) -> [a] -> [b]
mapPrePost f = mapWith' []
  where mapWith' pre [] = []
mapWith' pre (x:xs) = f pre xs : mapWith' (x:pre) xs

OK, you have to change the functions passed as f, and if f REALLY needs to
compute pre++xs then there is no gain, but I'm betting that in many cases
f has some property that enables

f' pre xs = f (pre++xs)

to be computed by a more efficient method.

John


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread D. Tweed
On Thu, 16 Jan 2003, Pal-Kristian Engstad wrote:

> It struck me though, if you have a function that calculates something on a
> list 'lst', and then you calculate something on 'lst ++ [a]', then surely one
> should be able to cache the results from the previous calculation.

I'm not a Haskell expert, but the code idea I posted (which was missing a
couple of arguments representing the initial `internal value's) was based
on a variant of this idea, namely move forward through the list producing
`internal values' (I'm trying to avoid using the phrase `internal state'
:-) )  for all prefixes of the list, then do the same for all the suffixes
of the list and combine the state for the prefix ending just before the
omitted item and the suffix beginning just after the omitted item to get a
full result. AFAICS this is O(n), whereas just doing prefixes this way
appears to still be quadratic because of the repeated evaluations of the
tail of the list.

Obviously being able to do this places some restrictions on what f can be
though.

___cheers,_dave_
www.cs.bris.ac.uk/~tweed/  |  `It's no good going home to practise
email:[EMAIL PROTECTED]  |   a Special Outdoor Song which Has To Be
work tel:(0117) 954-5250   |   Sung In The Snow' -- Winnie the Pooh

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread Adrian Hey
On Thursday 16 January 2003  4:10 pm, you wrote:
> I have a function which behaves like map, except instead of applying the
> given function to, say, the element at position 5, it applies it to the
> entire list *without* the element at position 5.  An implementation looks
>
> like:
> > mapWithout :: ([a] -> b) -> [a] -> [b]
> > mapWithout f = mapWith' []
> > where mapWith' pre [] = []
> >   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
>
> Unfortunately, this is very slow, due to the overhead of (++).

As an alternative to ++ I often use something like this..
 -- revJoin xs ys = (reverse xs) ++ ys
 revJoin [] ys = ys
 revJoin (x:xs) ys = revJoin xs (x:ys)

Which my intuition tells me will be faster overall because it avoids the
construction of thunks and the imperative (tail recusive) style probably
gives more cache friendly code. Of course whether or not this really is
better depends on context it's used. In your case using revJoin would
undo the reversal of pre in mapWith' (which may or may not be a good thing)
  
Regards
--
Adrian Hey
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread Janis Voigtlaender
Hal Daume III wrote:
> 
> I have a function which behaves like map, except instead of applying the
> given function to, say, the element at position 5, it applies it to the
> entire list *without* the element at position 5.  An implementation looks
> like:
> 
> > mapWithout :: ([a] -> b) -> [a] -> [b]
> > mapWithout f = mapWith' []
> > where mapWith' pre [] = []
> >   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
> 
> Unfortunately, this is very slow, due to the overhead of (++).

The following version avoids concatenations:

 mapWithout :: ([a] -> b) -> [a] -> [b]
 mapWithout f [] = []
 mapWithout f (x:xs) = f xs : mapWithout (\ys -> f (x:ys)) xs

but I doubt that you will see much speedup. 

> Any way I could speed this up would be great.  Note that order doesn't
> matter to 'f', but I do need that the order in which the elements of the
> list are processed be the same as in map.

The problem is that creating the "list of all sublists with one element
dropped" is inherently of quadratic complexity (or so I think...)
Nice puzzle though: how to minimize constant factors?

Cheers, Janis.


--
Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread Pal-Kristian Engstad
On Thursday 16 January 2003 08:10 am, Hal Daume III wrote:
> I have a function which behaves like map, except instead of applying the
> given function to, say, the element at position 5, it applies it to the
> entire list *without* the element at position 5.  An implementation looks
>
> like:
> > mapWithout :: ([a] -> b) -> [a] -> [b]
> > mapWithout f = mapWith' []
> > where mapWith' pre [] = []
> >   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs
>
> Unfortunately, this is very slow, due to the overhead of (++).

Sometimes, I find it easier to think about problems in C/C++. If I had a list 
in C, I would simply run f from the head of the list to the current split 
point, skip this one, then continue until the end of the list.

Notice that this gives O(n^2) complexity.

It struck me though, if you have a function that calculates something on a 
list 'lst', and then you calculate something on 'lst ++ [a]', then surely one 
should be able to cache the results from the previous calculation. 

For the same reason, if you have calculated f on '[a] + lst', you should be 
able to calculate the result on 'lst'.

For instance, if f = sum, then the basic operation is (+), so your mapWithout 
function should be equivalent to:

mapWithoutSum lst = let tot = sum lst in map (\x -> tot - x) lst

So, 

mapWithout :: ([a] -> b) -> (b -> a -> b) -> [a] -> [b]
mapWithout f g lst = 
let total = f lst in
map (g total) lst

mapWithoutSum' = mapWithout sum (\total x -> total - x)

Perhaps some Haskell expert can expand on this idea?

PKE.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread Zdenek Dvorak
Hello,


I have a function which behaves like map, except instead of applying the
given function to, say, the element at position 5, it applies it to the
entire list *without* the element at position 5.  An implementation looks
like:

> mapWithout :: ([a] -> b) -> [a] -> [b]
> mapWithout f = mapWith' []
> where mapWith' pre [] = []
>   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs

Unfortunately, this is very slow, due to the overhead of (++).

Any way I could speed this up would be great.  Note that order doesn't
matter to 'f', but I do need that the order in which the elements of the
list are processed be the same as in map.


two remarks:
1) as long as f works on single list, there is no way how to make things
  faster (IMHO)
2) this solution is up to constant factor optimal due to laziness (at most 
one
  step of ++ will be evaluated for each element f needs)

Zdenek Dvorak

_
Protect your PC - get McAfee.com VirusScan Online 
http://clinic.mcafee.com/clinic/ibuy/campaign.asp?cid=3963

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: avoiding cost of (++)

2003-01-16 Thread D. Tweed
On Thu, 16 Jan 2003, Iavor S. Diatchki wrote:

> hi,
>
> just for fun i wrote the function in a different way.  it should perform
> pretty much the same way as your function.  i don't think the problem is
> (++) here, it is just the way this function is.  if "f" is going to use
> all of its argument, it doesn't matter that you concatenated the two
> lists, as you will be walking over the list anyways.  if it is going to

The other obvious thing to ask is, given you say f doesn't care about the
order of its arguments, is whether you can write a version of f (f', say)
which `outputs its intermediate internal values' and another function
combineFStates which takes in two `internal values' and takes them to a
complete solution. Then at its very simplest (and very untested)

buildPartResults s f' [] = []
buildPartResults s f' (x:xs) = let e=f' s x
   in e:buildPartResults e f' xs

mapWithout combineFStates f' xs = zipWith combineFStates xs' (tail xs'')
 where xs'=buildPartResults f' xs
   xs''=buildPartResults f (reverse xs)

AFAICS this reuses the partial evaluations of f which, as Iavor suggests,
are likely to be very significant if the lists are long enough that the ++
shows up as costly. Obviously this won't help if f _isn't_ something where
internal states can be updated incrementally or the combining step isn't
easy.

Just a vague thought,

___cheers,_dave_
www.cs.bris.ac.uk/~tweed/  |  `It's no good going home to practise
email:[EMAIL PROTECTED]  |   a Special Outdoor Song which Has To Be
work tel:(0117) 954-5250   |   Sung In The Snow' -- Winnie the Pooh

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: avoiding cost of (++)

2003-01-16 Thread Iavor S. Diatchki
hi,

just for fun i wrote the function in a different way.  it should perform 
pretty much the same way as your function.  i don't think the problem is 
(++) here, it is just the way this function is.  if "f" is going to use 
all of its argument, it doesn't matter that you concatenated the two 
lists, as you will be walking over the list anyways.  if it is going to 
use only the first few elements, than becasue of lazyness (++) doesn't 
matter again.  you could avoid the linear concatenation by just using 
"zip" instead of "zipWith (++)" and making "f" take a pair of 
(before,after) elements, but as i said i don't see how that will speed 
up things, unless of course "f" wanted to, say only process the "after" 
elements.

import List(inits,tails)

mapWithout f [] = []
mapWithout f xs = map f (zipWith (++) (inits xs) (tails (tail xs)))

hope this helped
iavor


Hal Daume III wrote:
I have a function which behaves like map, except instead of applying the
given function to, say, the element at position 5, it applies it to the
entire list *without* the element at position 5.  An implementation looks
like:



mapWithout :: ([a] -> b) -> [a] -> [b]
mapWithout f = mapWith' []
   where mapWith' pre [] = []
 mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs



Unfortunately, this is very slow, due to the overhead of (++).

Any way I could speed this up would be great.  Note that order doesn't
matter to 'f', but I do need that the order in which the elements of the
list are processed be the same as in map.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell




--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



avoiding cost of (++)

2003-01-16 Thread Hal Daume III
I have a function which behaves like map, except instead of applying the
given function to, say, the element at position 5, it applies it to the
entire list *without* the element at position 5.  An implementation looks
like:

> mapWithout :: ([a] -> b) -> [a] -> [b]
> mapWithout f = mapWith' []
> where mapWith' pre [] = []
>   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs

Unfortunately, this is very slow, due to the overhead of (++).

Any way I could speed this up would be great.  Note that order doesn't
matter to 'f', but I do need that the order in which the elements of the
list are processed be the same as in map.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell