Fwd: [Haskell-cafe] What's the deal with Clean?

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.

On Tue, Nov 3, 2009 at 2:16 PM, Tracy Wadleigh
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

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
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

In the presence of fusion (as is the case in uvector), it's hard to
give meaningful time complexities for operations as they depend on
what operations they are paired with. We need to think of a better way
to express this behavior in the documentation though.
On Tue, Nov 3, 2009 at 9:12 PM, brian
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
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

On 04/11/2009, at 13:23, Daniel Peebles wrote:
In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired with. We need to think of a better way to express this behavior in the documentation though.
I have to disagree here. Fusion never makes the complexity of operations worse. If it does, it's a bug. Roman

Roman Leshchinskiy wrote:
On 04/11/2009, at 13:23, Daniel Peebles wrote:
In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired with. We need to think of a better way to express this behavior in the documentation though.
I have to disagree here. Fusion never makes the complexity of operations worse. If it does, it's a bug.
I think the point was more that the relevant complexity bound can change in the presence of fusion. For a poor example: the first map over a list is O(n) but all subsequent ones in a chain of maps are O(1) with fusion. I'm sure there are better examples than that, but you get the idea. Some people may care to know about that latter complexity rather than just the "independent" complexity. While this comes up with fusion, it's not a new problem. The same sort of thing is gotten at by distinguishing worst-case vs average-case complexity, or amortized worst-case vs non-amortized wost-case, etc. -- Live well, ~wren

On 04/11/2009, at 13:35, wren ng thornton wrote:
Roman Leshchinskiy wrote:
On 04/11/2009, at 13:23, Daniel Peebles wrote:
In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired with. We need to think of a better way to express this behavior in the documentation though. I have to disagree here. Fusion never makes the complexity of operations worse. If it does, it's a bug.
I think the point was more that the relevant complexity bound can change in the presence of fusion. For a poor example: the first map over a list is O(n) but all subsequent ones in a chain of maps are O(1) with fusion. I'm sure there are better examples than that, but you get the idea. Some people may care to know about that latter complexity rather than just the "independent" complexity.
I think asymptotic complexity is the wrong tool for what you're trying to do. You implement your algorithm using operations with known complexities. This allows you to compute the complexity of the entire algorithm. That's all you can use operation complexities for. The compiler is then free to optimise the algorithm as it sees fit but is supposed to preserve (or improve) its complexity. It is not guaranteed or even supposed to preserve the original operations. To stay with your example, each of the two maps is linear regardless of whether fusion happens. Executing the two maps, be it one after another or interlocked, is linear simply because O(n) + O(n) = O(n), not because of fusion. Essentially, you're trying to use complexity to describe an optimisation which doesn't actually affect the complexity. Roman

Roman Leshchinskiy wrote:
wren ng thornton wrote:
Roman Leshchinskiy wrote:
On 04/11/2009, at 13:23, Daniel Peebles wrote:
In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired with. We need to think of a better way to express this behavior in the documentation though.
I have to disagree here. Fusion never makes the complexity of operations worse. If it does, it's a bug.
I think the point was more that the relevant complexity bound can change in the presence of fusion. For a poor example: the first map over a list is O(n) but all subsequent ones in a chain of maps are O(1) with fusion. I'm sure there are better examples than that, but you get the idea. Some people may care to know about that latter complexity rather than just the "independent" complexity.
I think asymptotic complexity is the wrong tool for what you're trying to do. [...] Executing the two maps, be it one after another or interlocked, is linear simply because O(n) + O(n) = O(n), not because of fusion.
As I said, it was a bad example. Off-hand I can't think of any examples where fusion actually does affect asymptotic complexity rather than just reducing the constant factor. But I think such examples (if they exist) are what Daniel was concerned with, rather than any bugs where fusion makes the complexity (or constant factors) worse. -- Live well, ~wren

Actually, it's not a typo. If you look at the source, what you'll see is indexU arr n = indexS (streamU arr) n and then tracking down indexS, you'll see indexS (Stream next s0 _) n0 | n0 < 0 = error "Data.Array.Vector.Stream.indexS: negative index" | otherwise = loop_index n0 s0 where loop_index n s = case next s of Yield x s' | n == 0 -> x | otherwise -> s' `seq` loop_index (n-1) s' Skip s' -> s' `seq` loop_index n s' Done -> error "Data.Array.Vector.Stream.indexS: index too large" So in other words, indexU really does have O(n) complexity since it first converts the array into a stream and then walks down the stream in order to find the desired element. Cheers, Greg On Nov 3, 2009, at 6:25 PM, Roman Leshchinskiy wrote:
On 04/11/2009, at 13:12, brian wrote:
indexU :: UA e => UArr e -> Int -> e
O(n). indexU extracts an element out of an immutable unboxed array.
This is a typo (unless Don inserted a nop loop into the original DPH code).
Roman
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 04/11/2009, at 14:07, Gregory Crosswhite wrote:
Actually, it's not a typo. If you look at the source, what you'll see is
indexU arr n = indexS (streamU arr) n
I suspect it gets rewritten back to the O(1) version somewhere after
is has had a chance to fuse. If not, then it's a bug. In the vector
package, I do this instead, though:
indexU arr n =

Well, it depends on which indexU the OP means. The one linked in the docs is the O(1) UA type class version. -- Don gcross:
Actually, it's not a typo. If you look at the source, what you'll see is
indexU arr n = indexS (streamU arr) n
and then tracking down indexS, you'll see
indexS (Stream next s0 _) n0 | n0 < 0 = error "Data.Array.Vector.Stream.indexS: negative index" | otherwise = loop_index n0 s0 where loop_index n s = case next s of Yield x s' | n == 0 -> x | otherwise -> s' `seq` loop_index (n-1) s' Skip s' -> s' `seq` loop_index n s' Done -> error "Data.Array.Vector.Stream.indexS: index too large"
So in other words, indexU really does have O(n) complexity since it first converts the array into a stream and then walks down the stream in order to find the desired element.
Cheers, Greg
On Nov 3, 2009, at 6:25 PM, Roman Leshchinskiy wrote:
On 04/11/2009, at 13:12, brian wrote:
indexU :: UA e => UArr e -> Int -> e
O(n). indexU extracts an element out of an immutable unboxed array.
This is a typo (unless Don inserted a nop loop into the original DPH code).
Roman
_______________________________________________ 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

Oh, that's strange... the type class "UA" is defined twice, once in Data.Array.Vector and once in Data.Array.Vector.UArr; in the first module indexU is a separate function with the sources I exhibited, in the second module it is a method of the UA type-class which seems to have O(1) access for most of the defined instances. That's incredibly confusing... - Greg On Nov 3, 2009, at 9:15 PM, Don Stewart wrote:
Well, it depends on which indexU the OP means. The one linked in the docs is the O(1) UA type class version.
-- Don
gcross:
Actually, it's not a typo. If you look at the source, what you'll see is
indexU arr n = indexS (streamU arr) n
and then tracking down indexS, you'll see
indexS (Stream next s0 _) n0 | n0 < 0 = error "Data.Array.Vector.Stream.indexS: negative index" | otherwise = loop_index n0 s0 where loop_index n s = case next s of Yield x s' | n == 0 -> x | otherwise -> s' `seq` loop_index (n-1) s' Skip s' -> s' `seq` loop_index n s' Done -> error "Data.Array.Vector.Stream.indexS: index too large"
So in other words, indexU really does have O(n) complexity since it first converts the array into a stream and then walks down the stream in order to find the desired element.
Cheers, Greg
On Nov 3, 2009, at 6:25 PM, Roman Leshchinskiy wrote:
On 04/11/2009, at 13:12, brian wrote:
indexU :: UA e => UArr e -> Int -> e
O(n). indexU extracts an element out of an immutable unboxed array.
This is a typo (unless Don inserted a nop loop into the original DPH code).
Roman
_______________________________________________ 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

gcross:
Oh, that's strange... the type class "UA" is defined twice, once in Data.Array.Vector and once in Data.Array.Vector.UArr; in the first
No, its exported from the former.
module indexU is a separate function with the sources I exhibited, in the second module it is a method of the UA type-class which seems to have O(1) access for most of the defined instances.
That's incredibly confusing...
There's direct and stream-based versions. You can choose which version you need. If you use the stream-based implementations, the compiler will apply the stream fusion optimization to your loops. If you use the direct versions, that won't apply. I'd be happy to talk more about the design of the library, if you like. -- Don

Don Stewart wrote:
I'd be happy to talk more about the design of the library, if you like.
Don, I would be personally grateful if you could talk about the design of the library and/or point to some comprehensive documentation. Can you confirm that uvector is going to stay almost api compatible with dph, and that the knowledge investment is going to be "reusable" on dph? Paolo

On 07/11/2009, at 03:10, Paolo Losi wrote:
Don Stewart wrote:
I'd be happy to talk more about the design of the library, if you like.
Don,
I would be personally grateful if you could talk about the design of the library and/or point to some comprehensive documentation.
Can you confirm that uvector is going to stay almost api compatible with dph, and that the knowledge investment is going to be "reusable" on dph?
uvector has (almost) nothing in common with DPH's API. It is forked off the flat sequential array layer which DPH uses internally and which the users aren't supposed to even know about. Also, the fork happened quite a while ago, DPH has changed a lot since then and is going to change a lot more in the future. My plan is to eventually use my vector package to replace those flat arrays but sadly I don't have a lot of time to work on it (although vector is quite usable by now and even implements recycling which should improve DPH's performance by quite a bit). The fact that everything DPH depends on will have to be distributed with GHC doesn't help, either, since adding a new package into the mix is a pretty big step. Roman

Don, There is more than one indexU ? In Data.Array.Vector there is only 1 indexU that I can find. Brian On Nov 3, 2009, at 9:15 PM, Don Stewart wrote:
Well, it depends on which indexU the OP means. The one linked in the docs is the O(1) UA type class version.
-- Don
gcross:
Actually, it's not a typo. If you look at the source, what you'll see is
indexU arr n = indexS (streamU arr) n
and then tracking down indexS, you'll see
indexS (Stream next s0 _) n0 | n0 < 0 = error "Data.Array.Vector.Stream.indexS: negative index" | otherwise = loop_index n0 s0 where loop_index n s = case next s of Yield x s' | n == 0 -> x | otherwise -> s' `seq` loop_index (n-1) s' Skip s' -> s' `seq` loop_index n s' Done -> error "Data.Array.Vector.Stream.indexS: index too large"
So in other words, indexU really does have O(n) complexity since it first converts the array into a stream and then walks down the stream in order to find the desired element.
Cheers, Greg
On Nov 3, 2009, at 6:25 PM, Roman Leshchinskiy wrote:
On 04/11/2009, at 13:12, brian wrote:
indexU :: UA e => UArr e -> Int -> e
O(n). indexU extracts an element out of an immutable unboxed array.
This is a typo (unless Don inserted a nop loop into the original DPH code).
Roman
_______________________________________________ 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

UArr operations subject to stream fusion: http://code.haskell.org/~dons/code/uvector/Data/Array/Vector/Strict/ Direct-style operations, not subject to the optimization: http://code.haskell.org/~dons/code/uvector/Data/Array/Vector/UArr.hs /me needs to write a tutorial on this. -- Don briand:
Don,
There is more than one indexU ?
In Data.Array.Vector there is only 1 indexU that I can find.
Brian
On Nov 3, 2009, at 9:15 PM, Don Stewart wrote:
Well, it depends on which indexU the OP means. The one linked in the docs is the O(1) UA type class version.
-- Don
gcross:
Actually, it's not a typo. If you look at the source, what you'll see is
indexU arr n = indexS (streamU arr) n
and then tracking down indexS, you'll see
indexS (Stream next s0 _) n0 | n0 < 0 = error "Data.Array.Vector.Stream.indexS: negative index" | otherwise = loop_index n0 s0 where loop_index n s = case next s of Yield x s' | n == 0 -> x | otherwise -> s' `seq` loop_index (n-1) s' Skip s' -> s' `seq` loop_index n s' Done -> error "Data.Array.Vector.Stream.indexS: index too large"
So in other words, indexU really does have O(n) complexity since it first converts the array into a stream and then walks down the stream in order to find the desired element.
Cheers, Greg
On Nov 3, 2009, at 6:25 PM, Roman Leshchinskiy wrote:
On 04/11/2009, at 13:12, brian wrote:
indexU :: UA e => UArr e -> Int -> e
O(n). indexU extracts an element out of an immutable unboxed array.
This is a typo (unless Don inserted a nop loop into the original DPH code).
Roman
_______________________________________________ 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

briand:
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.
Umm.... That's a typo in the docs. Thanks. -- Don

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
On Tue, Nov 3, 2009 at 2:16 PM, Tracy Wadleigh
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/

How do you read in the IOUArray? By parsing a character string or do you treat the file as binary numbers or ... ? -- Jason Dusek

Jason Dusek wrote:
How do you read in the IOUArray? By parsing a character string or do you treat the file as binary numbers or ... ?
I always pare the file. Parsing the file has the advantage of alowing me to have files of any format. In general, in homeworks, TA generate files using different tools. For instance, a professor of electrical protection of hardware made a lot of measurements of transient currents due to lightning. The file has thousands of three column lines, each one containing time, voltage and current. Students are supposed to read the file, and plot voltage and current time series. Even the numbers are in a strange format... So, one needs to parse the file.
--- On Tue, 11/3/09, Jason Dusek

2009/11/4 Philippos Apolinarius
Jason Dusek wrote:
How do you read in the IOUArray? By parsing a character string or do you treat the file as binary numbers or ... ?
I always pare the file. Parsing the file has the advantage of alowing me to have files of any format.
From this description, it's hard for me to see what is hard for you. When you "parse the file" I imagine you in face "parse a String" or "parse a lazy ByteString" (a much better idea). Take that `String` or `ByteString` and pass it to an `ST` computation that parses it to make an `ST` array and then operates on the array. -- Jason Dusek

Let me see whether I understoodnd you correctly... If I read the contents of a file, the string will may be lazy (or something like that) and not consume memory? In fewer words, will the string behave like the infinite list of random numbers that I have used in the examples I posted?
--- On Wed, 11/4/09, Jason Dusek
Jason Dusek wrote:
How do you read in the IOUArray? By parsing a character string or do you treat the file as binary numbers or ... ?
I always pare the file. Parsing the file has the advantage of alowing me to have files of any format.
From this description, it's hard for me to see what is hard for you. When you "parse the file" I imagine you in face "parse a String" or "parse a lazy ByteString" (a much better idea). Take that `String` or `ByteString` and pass it to an `ST` computation that parses it to make an `ST` array and then operates on the array. -- Jason Dusek __________________________________________________________________ Make your browsing faster, safer, and easier with the new Internet Explorer® 8. Optimized for Yahoo! Get it Now for Free! at http://downloads.yahoo.com/ca/internetexplorer/

2009/11/04 Philippos Apolinarius
Let me see whether I understoodnd you correctly... If I read the contents of a file, the string will may be lazy (or something like that) and not consume memory?
A `String` or a lazy `ByteString` will be lazy and consume minimal memory. You can parse lazy `ByteString`s with AttoParsec. To the best of my knowledge, the most patched up and version of that parser is here: http://hackage.haskell.org/package/bytestringparser-temporary/ It is really in your best interest to parse with `ByteString`s instead of `String`s. Disclosure of conflict of interest: The package I mention is my own fork of Bryan O'Sullivan's AttoParsec (which is a little broken in places).
In fewer words, will the string behave like the infinite list of random numbers that I have used in the examples I posted?
In so far as it is lazy, yes. Lazy IO. A terrible idea, except when it's a good idea. -- Jason Dusek

On Nov 3, 2009, at 7:38 PM, Philippos Apolinarius wrote:
Really, arrays in Haskell are the most @#!$! confusing thing in
Brian wrote: 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
me too :-)
And here comes the reason for writing this article. In the previous version of the Gauss elimination algorithm, I have imported
you're asking me ?? I have no idea. I can't even figure out which package to use. However if I had to guess, it seems to me that you want to read the data into a list and then find some ST function which can initialize an array using a list (maybe ?) Brian

Brian wrote:
However if I had to guess, it seems to me that you want to read the data into a list and then find some ST function which can initialize an array using a list (maybe ?)
It is the other way around. I want to avoit lists. I would like to read the array elements from a file, and store then directly into the array. This approach would spare me from writing using a possibly expensive heap hungry intermediate structure.
--- On Tue, 11/3/09, brian
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
me too :-)
And here comes the reason for writing this article. In the previous version of the Gauss elimination algorithm, I have imported
you're asking me ?? I have no idea. I can't even figure out which package to use. However if I had to guess, it seems to me that you want to read the data into a list and then find some ST function which can initialize an array using a list (maybe ?) Brian __________________________________________________________________ Yahoo! Canada Toolbar: Search from anywhere on the web, and bookmark your favourite sites. Download it now http://ca.toolbar.yahoo.com.

On 04/11/2009, at 14:38, Philippos Apolinarius wrote:
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.
Why don't you use the IOUArray directly instead of converting it to STUArray and back? Roman

On Tue, 2009-11-03 at 18:12 -0800, brian wrote:
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.
Rather than confusing yourself with new packages like uvector I suggest you just use the arrays from the standard 'array' package that comes with GHC. It provides mutable and immutable, boxed and unboxed arrays. The mutable ones have to be used in a monad (ST or IO). The boxed ones can be used with any element type (eg an array of records) while unboxed ones work with simple primitive types like ints, floats etc. The difference is about memory layout and therefore performance: unboxed ones are simple flat C-like arrays while the boxed ones are arrays of pointers to heap objects. Duncan

Duncan Coutts
The boxed [array types] can be used with any element type (eg an array of records) while unboxed ones work with simple primitive types like ints, floats etc. The difference is about memory layout and therefore performance
...and of strictness. A boxed array can contain pointers to unevaluated thunks (including references to other cells in the array), an unboxed array only contains evaluated values. But yes, it'd be nice to tidy up the set of available array libraries, and perhaps related functionality (bytestring, text) to provide a unified and non-redundant, whole. Platform prime, anyone? -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (13)
-
brian
-
Daniel Peebles
-
David Leimbach
-
Don Stewart
-
Duncan Coutts
-
Gregory Crosswhite
-
Jason Dusek
-
Ketil Malde
-
Paolo Losi
-
Philippos Apolinarius
-
Roman Leshchinskiy
-
Tracy Wadleigh
-
wren ng thornton