Re: [Haskell] ST vs State

2007-05-30 Thread Federico Squartini

But they are very similar! At least superficially.

They are both based on the notion of state transformer. Moreover in
the original paper about the ST monad:
http://www.dcs.gla.ac.uk/fp/papers/lazy-functional-state-threads.ps.Z

The authors say:

"In this paper we describe a way to express stateful algorithms in
non-strict, purely functional languages".  And almost everywhere in
the paper looks as if they are talking about a normal State monad.

I suppose there is something "under the hood" which makes them
different, but I cannot figure out what.

Federico



Very very different.

-- Don


___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] ST vs State

2007-05-30 Thread Federico Squartini

Hello dear Haskellers,

Could someone be kind and explain with some detail what are the
differences between the two monads:

Control.Monad.ST
And
Control.Monad.State
?

They are both meant to model stateful computation but they are not the
same monad. The first one represents state with in place update?

Regards,

Federico
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell fast (?) arrays

2007-05-01 Thread Federico Squartini

Thanks for the hints. It's a pity that (as far as I know) no one has
written a tutorial on those techniques, because I think it would be
appreciated. Some of them are quite involved and learning them just by
reading code is very time consuming.


Federico
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell fast (?) arrays

2007-05-01 Thread Federico Squartini

Sorry, I was very silly!

This is the correct version of the program using the doFromto loop.
And it runs fast! I hope there are no further mistakes.
Thanks Axel.

time ./IOMutUnbUnsafe
499
real0m0.708s
user0m0.573s
sys 0m0.008s



-
-- compile with
-- ghc --make -o IOMutUnbUnsafe IOMutUnbUnsafe.hs
module Main
   where

import Monad
import Data.Array.IO
import Data.Array.MArray
import Data.Array.Unboxed
import Data.Array.Base ( unsafeWrite, unsafeRead )

total, semiTotal ::Int
total= 50
semiTotal=25


testArray :: IO (IOUArray Int Int)
testArray = newListArray (0,total)  [(19*i+23) `mod` 911 |i <- [0..total]]


reverseArray :: IOUArray Int Int -> IO ()
reverseArray arr = doFromTo 0 semiTotal (\i -> do oldi <- unsafeRead arr i

oldj <- unsafeRead arr (total-i)

unsafeWrite arr i oldj

unsafeWrite arr (total-i) oldi)

sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- unsafeRead arr i
return
$!(s+x) `mod` 911) 0 [0..total]


main::IO()
main = testArray >>= \a ->
  doFromTo 1 120 (\_ -> reverseArray a) >> sumArrayMod a >>=  print



{-# INLINE doFromTo #-}
-- do the action for [from..to], ie it's inclusive.
doFromTo :: Int -> Int -> (Int -> IO ()) -> IO ()
doFromTo from to action =
 let loop n | n > to   = return ()
| otherwise = do action n
 loop (n+1)
  in loop from

---

Federico
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Haskell fast (?) arrays

2007-05-01 Thread Federico Squartini

Of course I know that the list version is very unfair, but I wanted to see
what was the trade off between elegance and speed.
Regarding whether low level programming makes sense or not, I was just
curious to see what are the limits of Haskell. Moreover there is not much
literature on high performance Haskell programming (tricks like
unsafeWrite), at least organized in a systematic and concise way.

My original problem was writing a  fast library for simple matrix
computations (i.e. multiplication and inversion for small dense matrices).
I have not been able to make GSLHaskell work with Lapack so far. :(

Anyway here are the new versions and timings, I increased the number of
times the vector is reversed, I also compiled everything with -O2.

time ./arrayC
499
real0m0.244s
user0m0.236s
sys0m0.005s

time ./list
499
real0m11.036s
user0m10.770s
sys0m0.118s

time ./IOMutArrayUnboxed
499
real0m2.573s
user0m2.408s
sys0m0.042s

time ./IOMutUnbUnsafe
499
real0m2.264s
user0m2.183s
sys0m0.025s

--
--

//compile with g++ -O2 -o arrayC arrayC.cc
#include < stdio.h>
#include 



int main()
{
 int array[51];

 for (int i=0;i<=50;i++)
   {
   array[i]=(19*i+23)%911;
   }
 int tmp=0;
 for (int cnt=0;cnt<120;cnt++)
   {
 for (int x=0;x<=25;x++)
   {
 tmp=array[50-x];
 array[50-x]=array[x];
 array[x]=tmp;
   }
   }
 int result=0;
 for (int i=0;i<=50;i++)
   {
 result=result+(array[i]%911);
   }
 result=result % 911;
 printf("%d",result);
 return 0;
}




-- compile with
-- ghc -O2 --make -o list list.hs

module Main
   where

import Data.List

testArray = [ (19*i+23) `mod` 911 |i <- [0..50]]

sumArrayMod =  foldl (\x y -> (y+x) `mod` 911) 0

main = print $ sumArrayMod$
  foldl (.) id  (replicate 120 reverse) $testArray

--

-- compile with
-- ghc -O2 --make -o IOMutArrayUnboxed IOMutArrayUnboxed.hs
module Main
   where

import Monad
import Data.Array.IO 
import Data.Array.MArray
import Data.Array.Unboxed

total, semiTotal ::Int
total= 50 
semiTotal=25


testArray :: IO (IOUArray Int Int)
testArray = newListArray (0,total)  [(19*i+23) `mod` 911 |i <- [0..total]]


reverseArray :: IOUArray Int Int -> IO ()
reverseArray arr = mapM_  (\i -> do oldi <- readArray arr i
   oldj <- readArray arr (total-i)
   writeArray arr i oldj
   writeArray arr (total-i) oldi)
  [0..semiTotal]

sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- readArray arr i
   return   $!(s+x) `mod` 911) 0 [0..total]


main::IO()
main = testArray >>= \a ->
  sequence  (replicate 120 $reverseArray a)>>
  sumArrayMod a >>=  print




-- compile with
-- ghc -O2 --make -o IOMutUnbUnsafe IOMutUnbUnsafe.hs
module Main
   where

import Monad
import Data.Array.IO 
import Data.Array.MArray
import Data.Array.Unboxed
import Data.Array.Base ( unsafeWrite, unsafeRead )

total, semiTotal ::Int
total= 50 
semiTotal=25


testArray :: IO (IOUArray Int Int)
testArray = newListArray (0,total)  [(19*i+23) `mod` 911 |i <- [0..total]]


reverseArray :: IOUArray Int Int -> IO ()
reverseArray arr = mapM_  (\i -> do oldi <- unsafeRead arr i
   oldj <- unsafeRead arr (total-i)
   unsafeWrite arr i oldj
   unsafeWrite arr (total-i) oldi)
  [0..semiTotal]

sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- unsafeRead arr i
   return   $!(s+x) `mod` 911) 0 [0..total]



main::IO()
main = testArray >>= \a ->
  doFromTo 1 120 (\_ -> reverseArray a) >> sumArrayMod a >>=  print



{-# INLINE doFromTo #-}
-- do the action for [from..to], ie it's inclusive.
doFromTo :: Int -> Int -> (Int -> IO ()) -> IO ()
doFromTo from to action =
 let loop n | n > to   = return ()
| otherwise = do action n
 loop (n+1)
  in loop from

---
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Haskell fast (?) arrays

2007-05-01 Thread Federico Squartini

I was reading an old post where Hal Daume III was analyzing Haskell
performance for arrays.
He proposed a test program which initializes an array, reverse it a number
of times, and sums the contents.

So I wrote a c++ reference program, a naive haskell version using lists and
I also tweaked a little bit with the IOArray version, which should be the
fastest. Unfortunately there is a  huge performance gap. Haskell is slower
by a factor of ten, even when using imperative style.

C++
time ./arrayC
499
real0m0.059s
user0m0.044s
sys0m0.008s

HASKELL - IOUArray
time ./IOMutArrayUnboxed
499
real0m0.720s
user0m0.571s
sys0m0.019s

HASKELL - list
time ./list
499
real0m1.845s
user0m1.770s
sys0m0.064s


Can anyone suggest a faster version (using whatever data structure)? I like
Haskell very much but I still have to figure out if the slowness of some
code is due to my lack of knowledge or to some intrinsic limitation of the
language (or libraries).

By the way, sorry for the poor quality of the code, I am not a computer
scientist.


---

---
//compile with
//g++ -o arrayC arrayC.cc
#include 
#include < math.h>



int main()
{
 int array[51];

 for (int i=0;i<=50;i++)
   {
   array[i]=(19*i+23)%911;
   }
 int tmp=0;
 for (int cnt=0;cnt<12;cnt++)
   {
 for (int x=0;x<=25;x++)
   {
 tmp=array[50-x];
 array[50-x]=array[x];
 array[x]=tmp;
   }
   }
 int result=0;
 for (int i=0;i<=50;i++)
   {
 result=result+(array[i]%911);
   }
 result=result % 911;
 printf("%d",result);
 return 0;
}

-

-
-- compile with
-- ghc --make -o list list.hs
module Main
   where

testArray = [ (19*i+23) `mod` 911 |i <- [0..50]]

sumArrayMod =  foldl (\x y -> (y+x) `mod` 911) 0

main = print $ sumArrayMod$
  reverse$ reverse$ reverse$ reverse$
  reverse$ reverse$ reverse$ reverse$
  reverse$ reverse$ reverse$ reverse$
  reverse$ reverse$ reverse$ reverse$
  testArray


-

-
-- compile with
-- ghc --make -o IOMutArrayUnboxed IOMutArrayUnboxed.hs
module Main
   where

import Monad
import Data.Array.IO
import Data.Array.MArray
import Data.Array.Unboxed

total, semiTotal ::Int
total= 50
semiTotal=25


testArray :: IO (IOUArray Int Int)
testArray = newListArray (0,total)  [(19*i+23) `mod` 911 |i <- [0..total]]


reverseArray :: IOUArray Int Int -> IO ()
reverseArray arr = mapM_  (\i -> do oldi <- readArray arr i
   oldj <- readArray arr (total-i)
   writeArray arr i oldj
   writeArray arr (total-i) oldi)
  [0..semiTotal]

sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- readArray arr i
 return   $!(s+x)
`mod` 911) 0 [0..total]


main::IO()
main = testArray >>= \a ->
  reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a



  reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a



  reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a



  reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a



  sumArrayMod a >>=  print

-

Federico
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell