[Haskell-cafe] Array functions?

Cale Gibbard cgibbard at gmail.com
Tue May 3 21:03:16 EDT 2005


The first thing that I think I should mention is that lists are not
arrays. You should have a look at Data.Array
(http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Array.html)
and the other libraries in that bunch if you really want arrays (where
random access is O(1) rather than O(n))

Now, your "find" function is implemented as a library function, it is
called (!!) so xs !! n is the nth element of a list xs.

What I think you intend by index is implemented in Data.List as
elemIndex, which returns a Maybe Int, that is the value (Just n) if
the first occurrence of the desired element is at position n, and the
value (Nothing) otherwise.

Finding and then swapping two elements of a Haskell list is not a
terribly efficient thing to do.

If I had to do it directly, I'd probably write something like:

import List
swap i j xs | i == j    = xs
swap i j xs | otherwise = initial ++ (xs !! b) : middle ++ (xs !! a) : end 
    where [a,b] = sort [i,j]
          initial = take a xs
          middle  = take (b-a-1) (drop (a+1) xs)
          end     = drop (b+1) xs

which takes time and space on the order of b.

The need to do lots of swaps is probably an indication that a list is
not the data structure you're looking for though. What are you
actually trying to accomplish? There are a number of other data
structures readily available.

Have a look at the hierarchical libraries at
http://www.haskell.org/ghc/docs/latest/html/libraries/index.html
in particular at Data.Map, Data.Set, and Data.Array.*

hope this is useful :)
 - Cale

On 5/3/05, Daniel Carrera <dcarrera at digitaldistribution.com> wrote:
> Hello,
> 
> I hope these don't turn out to be RTFM questions, but I can't find them
> in my FM :-)
> 
> 1) Is there a function to get the ith element from an array?
> 2) Is there a function to get the "index" of an entry in an array?
> 
> I've implemented these two functions below:
> 
> 1)
> find 0 (x:xs) = x
> find n (x:xs) = find (n-1) xs
> 
> 2)
> index i (x:xs) =
>     if i == x
>       then 0
>       else 1 + index a xs
> 
> This was a fun exercise, but I can't shack off the feeling that I just
> re-invented the wheel.
> 
> I need these because I want to be able to swap any two elements from an
> array. This is my swap function:
> 
> -- swap i j array   =>  swaps the ith and jth elements of 'array'.
> --
> swap i j arr = a_head ++ [item_j] ++ a_midd ++ [item_i] ++ a_tail
>     where a_head = [a | a <- arr, index a arr  < i]
>           item_i = find i arr
>           a_midd = [a | a <- arr,(index a arr  > i) && (index a arr < j)]
>           item_j = find j arr
>           a_tail = [a | a <- arr, index a arr  > j]
> 
> I'm sure this was a poor way to accomplish this, but it was a learning
> experience. If anyone would like to show me a more elegant solution, I
> would be happy to see it.
> 
> Cheers,
> Daniel.
> Haskell newbie.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list