Brian wrote:
> Really, arrays in Haskell are the most @#!$! confusing thing in the world.

Hi, Brian. 
I am having a great difficulty with arrays in Haskell.  In the university where 
I study, functional programming is taught in Clean or in Haskell, depending on 
the professor who is teaching the subject in a given year. One year ago, when I 
took functional programming, the professor used Clean in his classes. I had no 
difficulty in learning how arrays and input/output work in Clean.  In the case 
of arrays, the idea is very simple: One can update arrays, provided that s/he 
does not try to access the old array. Therefore, one needs to make a copy of 
any value of the old array that s/he will use before performing the update; the 
operation that makes copies also provides a new name for the array, that 
obliterates the old name.  In order to get a better feeling of the thing, here 
is the `solvit´ function, in Clean and Haskell (you can consider the # as a 
kind of do):

// Clean
leftSide acc i j n arr | j >= n= (acc, arr);
   # (v, arr)= arr![j, n];
     (a, arr)= arr![i, j];
   = leftSide (acc-v*a) i (j+1) n arr;

solvit i n arr | i < 0 = arr
  # (a, arr)= arr![i, i];
    (acc, arr)= arr![i, n];
    (v, arr)= leftSide acc i (i+1) n arr;
  = solvit (i-1) n {arr&[i, n]= v/a};

-- HASKELL
leftSide acc i j n arr | j>n= return acc
leftSide acc i j n arr = do
   v <- readArray arr (j, n+1)
   a <- readArray arr (i, j)
   leftSide (acc-v*a) i (j+1) n arr

solvit i n arr | i<1= return ()
solvit i n arr= do
   a <- readArray arr (i, i)
   acc <- readArray arr (i, n+1)
   v <- leftSide acc i (i+1) n arr
   writeArray arr (i, n+1) $! (v/a)
   solvit (i-1) n arr

And here comes the reason for writing this article. In the previous version of 
the Gauss elimination algorithm, I have imported Data.Array.IO. I also wrote a 
version of the program that imports Data.Array.ST. The problem is that I  don't 
know how to read an STUArray from a file, process it, and write it back to a 
file. Is it possible to transform it into an IOUArray pro tempore, read it, 
make it into an STUArray again in order to process it, and bring it back to 
IOUArray in order to print it? Below,  you will find the Gauss elimination 
program in STUArray (by the way, it is slower than IOUArray). Could you modify 
the main function so it can read array `arr´ from a file, and write the result 
to a file?  Here is the Gauss Elimination for STUArray (the main function is 
the first one; modify it to read the array from a file, and write it back to a 
file):

import Control.Monad
import Control.Monad.ST
import Data.Array.ST
import Data.Array.IO 
import System.IO
import System.Random
import System (getArgs)


main = do
     xs <- rnList (1.0,1000.0)
     args <- getArgs
     let (n, m)= dims args
     xx <-  stToIO $ do
                 arr <- newArray_ ((1,1),(n,m+1)) :: 
                   ST s (STUArray s (Int, Int) Double)
                 fillArray xs 0.0 (1,n) (1,m) arr
                 sLU arr n
                 solvit n n arr
                 x1 <- readArray arr (1, n+1)
                 x2 <- readArray arr (1, n+1)
                 return [x1, x2]
     print xx


{-  -- Other option:
main = do
     xs <- rnList (1.0,1000.0)
     args <- getArgs
     let (n, m)= dims args
     print $ runST $ do
                 arr <- newArray_ ((1,1),(n,m+1)) :: 
                   ST s (STUArray s (Int, Int) Double)
                 fillArray xs 0.0 (1,n) (1,m) arr
                 sLU arr n
                 solvit n n arr
                 x1 <- readArray arr (1, n+1)
                 x2 <- readArray arr (1, n+1)
                 return [x1, x2]
-}   

fillArray xs s (i, n) (j, m) arr |  i > n= return ()
fillArray xs s (i,n) (j, m) arr | i==n && j>m= do
  writeArray arr (i, j) $! s
  return ()
fillArray xs s (i, n) (j, m) arr | j > m  = do
   writeArray arr (i, j) $! s
   fillArray xs 0.0 (i+1, n) (1, m) arr
fillArray (val:xs) s (i, n) (j, m) arr= do
   writeArray arr (i, j) $! val
   fillArray xs (s+val) (i, n) (j+1, m) arr

sLU arr n= sIJ 2 1 2 n arr

sIJ i j k n arr | i > n = return ()
sIJ i j k n arr | k > n = sIJ (i+1) i (i+1) n arr
sIJ i j k n arr = do
 {- im <- pmax (j+1) j
  swap j im 1 -}
  a <- readArray arr (k, j)
  forM_ [j..n+1] $  \l -> do
      ajj <- readArray arr (j, j)
      ajl <- readArray arr (j, l)
      akl <- readArray arr (k, l) 
      writeArray arr (k, l) $! (akl-a*(ajl/ajj))
  sIJ i j (k+1) n arr where
     pmax line imax | line > n = return imax
     pmax line imax = do
       alj <- readArray arr (line, j)
       aij <- readArray arr (imax, j)
       if (abs alj)> (abs aij) 
          then pmax (line+1) line
          else pmax (line+1) imax
     swap r s q | q>n+1 = return ()
     swap r s q | r==s = return ()
     swap r s q = do
        arq <- readArray arr (r,q)
        asq <- readArray arr (s,q)
        writeArray arr (s,q) $! arq
        writeArray arr (r,q) $! asq
        swap r s (q+1)
     
  
leftSide acc i j n arr | j>n= return acc
leftSide acc i j n arr = do
   v <- readArray arr (j, n+1)
   a <- readArray arr (i, j)
   leftSide (acc-v*a) i (j+1) n arr

solvit i n arr | i<1= return ()
solvit i n arr= do
   a <- readArray arr (i, i)
   acc <- readArray arr (i, n+1)
   v <- leftSide acc i (i+1) n arr
   writeArray arr (i, n+1) $! (v/a)
   solvit (i-1) n arr

rnList :: (Double, Double) -> IO [Double]
rnList r=getStdGen>>=(\x->return(randomRs r x))

dims [input] = (read input, read input)
dims _ = (1000, 1000)





--- On Tue, 11/3/09, brian <bri...@aracnet.com> wrote:

From: brian <bri...@aracnet.com>
Subject: Re: [Haskell-cafe] What's the deal with Clean?
To: "David Leimbach" <leim...@gmail.com>
Cc: haskell-cafe@haskell.org
Received: Tuesday, November 3, 2009, 7:12 PM

Really, arrays in Haskell are the most @#!$! confusing thing in the world.

There's a bunch of different array structures.

I can't tell which one works best, and all I want to do is x[i] = value.

I thought uvector was the answer, you know, fast unboxed ARRAYs.  Imagine my 
surprise when I saw this

  indexU :: UA e => UArr e -> Int -> e

  O(n). indexU extracts an element out of an immutable unboxed array.

An array implementation with an order N lookup.  huh ??  That's not an array, 
that's a list.  I was looking for an array.

However, I then found in the same hackage:

  readMU :: MUArr e s -> Int -> ST s e

  O(1). readMU reads the element at the specified index of a mutable unboxed 
array.

So O(1) for mutable, but O(n) for immutable ? See, confusing...  I'm sure 
there's a really good, lofty type safety, something
or other reason for that, that I'm sure I don't care about ;-)

There's also ST.  So why is there a uvector, when there's ST ??

etc, etc, etc...

and then there's monads...

other than that, having fun with haskell :-)

Brian


On Nov 3, 2009, at 3:42 PM, David Leimbach wrote:

> 
> 
> On Tue, Nov 3, 2009 at 2:16 PM, Tracy Wadleigh <tracy.wadle...@gmail.com> 
> wrote:
> 
> I had to implement a ring buffer, and I wanted the code using it to be 
> written in Haskell.  I ended up implementing the buffer in C, and wrapping it 
> in FFI from Haskell because implementing a destructive array in Haskell is 
> kind of unwieldy to someone of my experience level.  In Clean, it looks like 
> the uniqueness typing allows for destructive updates in a very controlled 
> manner.
> 
> The ST monad provides this functionality. The 
> never-instantiated-in-a-visible-way state parameter of the ST monad provides 
> the "uniqueness" required for doing destructive updates in a pure way.
> 
> Someone suggested that to me on IRC once I'd already cranked out a C 
> implementation with FFI bindings.  It's just too easy to use the FFI in 
> Haskell :-)
> 
> If we raise the barrier of FFI, more people will use ST!
> 
> Dave
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



      __________________________________________________________________
Get the name you've always wanted @ymail.com or @rocketmail.com! Go to 
http://ca.promos.yahoo.com/jacko/
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to