Re: [Haskell-cafe] type families, fun deps, lattices imposed on/by types

2008-03-18 Thread Isto Aho
Hi  thanks for your answers Manuel,

Using your idea of separating the lattice and conversion from the
 definition of multiplication, you can at least save yourself the class
 instances:


Ok

  type family Join a b :: *


Aah, meet and join but of course - memory memory memory seems
to get easily corrupted... :)


is more flexible, as I am sure there are other applications, where we
 don't want a lattice, but some other structure.


Yes, and then there can be cases where we don't know exactly, what we want
or there are situations where two almost but not identical structures are
needed.

   http://www.cse.unsw.edu.au/~pls/thesis/aja-thesis.pdf


Thanks again! I'll try to read it quite soon.

-- 
br,
Isto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-08-01 Thread Isto Aho
Hi,

I'd like to store small matrices into a db. Number of rows and columns may
vary in a way not
known in advance. One might use a relation (matrixId, col, row, value) or
something like that
but if it is possible to put a matrix in one command into db, some queries
will be easier.
E.g., one relation can store several matrices and it would be easy to query,
how many
matrices are stored currently. With that above four tuple you can find out
the number of unique
matrixId's, too, but it is not as easy as with matrices.

Anyhow, now I'm not sure if I should stick with HSQL any more... Earlier
comments on this
thread made me think that maybe it would be a better idea to try to learn
enough HDBC.

This would be used in a server application. Is HAppS applicable here?

e.g. after some tweaking the following works with HSQL:

addRows = do
dbh - connect server database user_id passwd
intoDB dbh ([555,111, 50, 1000]::[Int]) ([21.0,22.0,23.0,24.0
]::[Double])
intoDB dbh ([556,111, 50, 1000]::[Int]) ([21.0,22.0,23.0,24.0
]::[Double])
intoDB dbh ([]::[Int]) ([]::[Double])
   where
intoDB dbh i_lst d_lst =
catchSql (do
let cmd = INSERT INTO trial (intList, dList) VALUES
( ++
toSqlValue i_lst ++ , ++ toSqlValue d_lst
++ )
execute dbh cmd
)
(\e - putStrLn $ Problem:  ++ show e)


Similarly, queries can handle matrices and I like that it is now
possible to select those columns or rows from the stored matrix that
are needed.  E.g.

retrieveRecords2 :: Connection - IO [[Double]]
retrieveRecords2 c = do
-- query c select dList[1:2] from trial = collectRows getRow
query c select dList from trial = collectRows getRow
where
getRow :: Statement - IO [Double]
getRow stmt = do
lst   - getFieldValue stmt dList
return lst
readTable2 = do
dbh - connect server database user_id passwd
values - retrieveRecords2 dbh
putStrLn $ dLists are :  ++ (show values)


br,
Isto


2007/8/1, Alex Jacobson [EMAIL PROTECTED]:

 Out of curiosity, can I ask what you are actually trying to do?

 I am asking because I am trying to make HAppS a reasonable replacement
 for all contexts in which you would otherwise use an external relational
 database except those in which an external SQL database is a specific
 requirement.

 -Alex-


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


Re: [Haskell-cafe] Re: HDBC or HSQL

2007-07-30 Thread Isto Aho
Hi,

I was also wandering between these different db-libs and thanks for your
information.

I tried several (HDBC, HSQL, HaskellDB) and made only small trials.
HaskellDB has quite many examples on wiki that gave a quick start to further
trials.
But, I wasn't able to tell that some of the fields have default values and
then it
was already time to move on to the HSQL and HDBC trials.

Is it possible to use sql-array-types with HDBC with postgresql? I don't
remember was this the
reason why I eventually tried HSQL - anyhow, it was rather difficult to get
started with HDBC
but the src test cases helped here. One example in a wiki would do miracles
:)

HSQL didn't have the array-types but it took only couple of hours to add a
sort of support
for those. There are some problems though... (indexed table queries
returning some nulls
is not yet working and ghci seems to be allergic to this)  I was even
wondering, should I propose
a patch in some near future for this.

But if HDBC can handle those sql-arrays or if you can give a couple of
hints, how to proceed
in order to add them there, given your view below, I'd be willing to try to
help / to try to use HDBC.

br,
Isto

2007/7/30, John Goerzen [EMAIL PROTECTED]:

 On 2007-07-25, George Moschovitis [EMAIL PROTECTED] wrote:
  I am a Haskell newbie and I would like to hear your suggestions
 regarding a
  Database conectivity library:
 
  HSQL or HDBC ?
 
  which one is better / more actively supported?

 I am the author of HDBC, so take this for what you will.

 There were several things that bugged me about HSQL, if memory serves:

 1) It segfaulted periodically, at least with PostgreSQL

 2) It had memory leaks

 3) It couldn't read the result set incrementally.  That means that if
 you have a 2GB result set, you better have 8GB of RAM to hold it.

 4) It couldn't reference colums in the result set by position, only by
 name

 5) It didn't support pre-compiled queries (replacable parameters)

 6) Its transaction handling didn't permit enough flexibility

 I initially looked at fixing HSQL, but decided it would be easier to
 actually write my own interface from scratch.

 HDBC is patterned loosely after Perl's DBI, with a few thoughts from
 Java's JDBC, Python's DB-API, and HSQL mixed in.

 I believe it has fixed all of the above issues.  The HDBC backends that
 I've written (Sqlite3, PostgreSQL, and ODBC) all use Haskell's C memory
 management tools, which *should* ensure that there is no memory leakage.

 I use it for production purposes in various applications at work,
 connecting to both Free and proprietary databases.  I also use it in my
 personal projects.  hpodder, for instance, stores podcast information in
 a Sqlite3 database accessed via HDBC.  I have found HDBC+Sqlite3 to be a
 particularly potent combination for a number of smaller projects.

 http://software.complete.org/hdbc/wiki/HdbcUsers has a list of some
 programs that are known to use HDBC.  Feel free to add yours to it.

 -- John

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




-- 
br,
Isto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Writing Haskell For Dummies Or At Least For People Who Feel Like Dummies When They See The Word 'Monad'

2006-12-14 Thread isto
ke, 2006-12-13 kello 08:18 -0800, Justin Bailey kirjoitti:
 On 12/12/06, Joachim Durchholz [EMAIL PROTECTED] wrote:
 Agreed.
 Something along the lines of The Art of Functional
 Programming.
 
 +1 . I would love to read something that is the equivalent of 'design
 patterns',  but for functional languages. I thought Osasaki's book 

Hi,

Would the following fit the need?
http://www.cs.vu.nl/Strafunski/
http://www.cs.vu.nl/Strafunski/dp-sf/

br, Isto

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


Re: [Haskell-cafe] On improving libraries: wanted list

2006-12-11 Thread isto
ma, 2006-12-11 kello 11:52 +1100, Donald Bruce Stewart kirjoitti:
 http://haskell.org/haskellwiki/Wanted_libraries

 A good constructive list here will help focus developer efforts, and
 someone may just step up with the code!

Hi Don,

I couldn't agree more on this :)  

About 'Wanted' page: would it be possible to easily have an 
index being up-to-date reporting the activity status of each lib?
Either in this 'Wanted' page or somewhere else like in the 
liblistpage. 

For example, first it seems that there are plenty of nice math
libraries but then it is harder to choose which one to use because
one does not see right away, which are still actively developed and
which are more or less on their own on the bit space...
e.g. date of the last revision could be on the end of title 
or first thing on the description?

Another thing somebody might would like to see easily is the license
e.g. as a last word on the title?

Could/can Cabal tell all this to me with one command?  That is, give a
list of available libraries to be downloaded with their versions,
licences and current #downloads? :)  

br, Isto


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


Re: [Haskell-cafe] Optimizing a hash function

2006-11-26 Thread isto
su, 2006-11-26 kello 15:12 +1100, Ivan Tomac kirjoitti:
 The first version I came up with ran 20 times slower than C.
 Thanks to Don Stewart's suggestions on IRC, I managed to improve the  
 ...

 Options used to compile the version using the hash function written  
 in Haskell:
 ghc -O -funbox-strict-fields -fglasgow-exts -fbang-patterns -cpp -o  
 test hashByteString.hs test.hs
 
 Options used to compile the version using the hash function in C:
 ghc -O -fglasgow-exts -ffi -fbang-patterns -cpp -DCHASH -o ctest  
 ctest.c test.hs

Hi Ivan Tomac,

Have you tried -O3 -optc-O3  -funfolding-use-threshold=16 
compile flags?  Don, Lemmih, Lennart and Bulat helped me to sort
out a similar problem a couple of weeks ago. More hints can be found at
http://haskell.org/haskellwiki/Performance/GHC
Especially, to check generated code by taking a look of core
-ddump-simpl  core.txt
and to check memory leaks, you could run with
+RTS -sstderr

br, Isto

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


Re: [Haskell-cafe] Difficult memory leak in array processing

2006-11-23 Thread isto
Hi Niko,

to, 2006-11-23 kello 12:11 +0200, Niko Korhonen kirjoitti:
 I've tried applying seq and some other strictness tricks (such as x ==
 x) pretty much everywhere on the code with no results. Could you
 please help me understand what is going on here? Have I misunderstood
 something critical in how Haskell works? Here is the relevant portion
 of the code: 

 main = do
 -- This should allocate a 40 MB array
 buf - newArray_ (0, 1000) :: IO Buffer
 -- Fill the array with dither 
 genSeries buf tpdf (2, 12)


main = do
-- This should allocate a 40 MB array
buf - newArray_ (0, 1) :: IO Buffer
-- Fill the array with dither 
genSeries buf tpdf (2, 12)
a - readArray buf  1
putStrLn $ a is  ++ (show a)

By adding -O3 -optc-O3  -funfolding-use-threshold=16 
compile flags the above code with 100'000'000 elements
worked.  And by still adding -ddump-simpl  core.txt
flag and looking the generated core, the worker-loop 
seemed to use primitives.

I cannot say, if this was the helping part here.  Have you
tried profiling: -prof -auto-all  and running with +RTS -p -RTS?
Or running with  +RTS -sstderr
gives

14,257,786,344 bytes allocated in the heap
  4,282,040 bytes copied during GC (scavenged)
  1,646,936 bytes copied during GC (not scavenged)
 80,733,232 bytes maximum residency (2 sample(s))

  27045 collections in generation 0 (  0.31s)
  2 collections in generation 1 (  0.00s)

 78 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time   22.61s  ( 24.07s elapsed)
  GCtime0.31s  (  0.32s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time   22.92s  ( 24.39s elapsed)

  %GC time   1.3%  (1.3% elapsed)

  Alloc rate630,612,876 bytes per MUT second

  Productivity  98.6% of total user, 92.7% of total elapsed


It seems that garbage collector has not used very much time here.
There is more information on haskell wiki:
http://www.haskell.org/haskellwiki/Performance
http://www.haskell.org/haskellwiki/Performance/GHC

This GHC specific part does not mention -O3 -optc-O3
-funfolding-use-threshold=nn flags.  They were hinted here
on this list; I have found them very helpful a couple of weeks 
ago - thanks again :)
btw, Could the GHC specific wiki page be updated to contain and
explain these flags?

Hopefully this helped you a bit!  And hopefully someone who knows
how these things go have time to give you a detailed answer!

br, Isto

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


[Haskell-cafe] list monad and controlling the backtracking

2006-11-23 Thread isto
Hi all,

Weekly news had a link to article
Local and global side effects with monad transformers
and the following is from there (minor modification done):

import Control.Monad.List
import Control.Monad.State
import Control.Monad.Writer

test5 :: StateT Integer (ListT (Writer [Char])) Integer

test5 = do
 a - lift $ mlist aList
 b - lift $ mlist bList
 lift $ lift $ tell (trying ++show a++ ++show b++\n)
 modify (+1)
 guard $ a+b5
 return $ a+b

go5 = runWriter $ runListT $ runStateT test5 0


If the aList = [1..5] as well as bList, then there will be 25 tryings.
If aList and bList are [1..1000], there will be a lot of tryings...

However, guard is saying that we are interested in only values
whose sum is less than 5. 

Is it possible to control easily in the above example that when we 
have tried out pairs (1,1), (1,2), (1,3), (1,4), that now we are 
ready to stop trying from the bList?  And then similarly when we
finally arrive to a pair (4,1), that now we are ready to finish
also with aList?  

This would give a nice way to build branch  bounding algorithms,
even though it does not take much more lines to do it in some other way.

br, Isto



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


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-23 Thread isto
Hi  thanks!


to, 2006-11-16 kello 14:02 -0800, Greg Buchholz kirjoitti:
 ] I'll guess the reason it didn't compile was different
 ] types at case branches (am I wrong?) 
 
 Correct.
 
 ] Anyhow, do you know that is it possible to choose the return type
 ] somehow in the spirit above?  
 
 Maybe you want something like...

This time, however, I'm not sure after seeing oleg's email:
  http://www.haskell.org/pipermail/haskell/2006-November/018736.html

I'll have yet to re-read it carefully to be sure... :)

br, Isto



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


Re: [Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-16 Thread isto
ke, 2006-11-15 kello 13:31 -0800, Greg Buchholz kirjoitti:
 isto wrote:
 ] let t = show (typeOf a)
 ] in case t of
 ] Double  - roundDDec d a
 ] Complex Double - roundCDec d a

 Maybe you want type classes instead?

 yes, I was blind... Thanks! 

I'll guess the reason it didn't compile was different
types at case branches (am I wrong?) Anyhow, do you know that 
is it possible to choose the return type somehow in the spirit 
above?  

br, Isto


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


[Haskell-cafe] type keeping rounding, typeable (and a difficulty)

2006-11-15 Thread isto
Hi,

I've been trying to compile the following function
(rounding to a desired degree):

roundDec :: (Num a, Typeable a) = Int - a - a
roundDec d a = 
let t = show (typeOf a)
in case t of
Double  - roundDDec d a
Complex Double - roundCDec d a
otherwise - a  -- or something

The two other functions are 

roundCDec :: (RealFloat a) = Int - Complex a - Complex a
roundCDec d (c :+ b) = (roundDDec d c :+ roundDDec d b)
and
roundDDec :: (RealFloat a) = Int - a - a
roundDDec d a = a  -- or somegthing

Compiler gives the following error message:
Couldn't match expected type `Complex a'
   against inferred type `a1' (a rigid variable)
  `a1' is bound by the type signature for `roundDec' at FFT.hs:57:17
In the second argument of `roundCDec', namely `a'
In the expression: roundCDec d a
In a case alternative: Complex Double - roundCDec d a

If in the roundDDec a's are replaced with Double, there will
be similar error message from the Double-line.  The functionality
can be written differently, but I wanted to try write rounding
having in a signature at least (Num a) = Int - a - a.

Again, any help would be appreciated a lot! Thanks in advance!

br, Isto


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


[Haskell-cafe] 64bit code output is less optimized than 32bit in ghc?

2006-11-05 Thread isto
Hi again,

Still playing with the Mersenne Twister and here is the
updated 64 bit version so that there are not so many 
constructor calls on next64 (together with updated
compiling flags). 

I was wondering why different runs can have such different
run times and the cause was found to be my system: also the
C version running times can vary (usually 0.65 but sometimes 0.3).

The 64 bit version took usually about 1.1 or 1.2 seconds while
32bit version required only 0.78 (against 0.65 with C for both
32 and 64 bit versions).

Since the real work horse here is the next64 function, I took a
look of Core.  There seems to be an extra case-statement in
64bit version and this might explain the performance drop (about
6 or 7 lines below _DEFAULT text on both versions below). 
Relevant parts of the Core below, code attached.  It is very 
possible that I'm missing something obvious here.

So what is happening here?  :)  

Thanks again for any comments!  

br, Isto

 Core (32 and 64 nexts)
Rec {
Mersenne.$wnext64 :: Data.Array.IO.Internals.IOUArray GHC.Base.Int
  GHC.Word.Word64
 - GHC.Prim.Int#
 - GHC.Prim.State# GHC.Prim.RealWorld
 - (# GHC.Prim.State# GHC.Prim.RealWorld, (GHC.Word.Word64,
GHC.Base.Int) #)
[GlobalId]
[Arity 3
 Str: DmdType LLL]
Mersenne.$wnext64 =
  \ (w_s2Zq :: Data.Array.IO.Internals.IOUArray GHC.Base.Int
GHC.Word.Word64)
(ww_s2Zt :: GHC.Prim.Int#)
(w1_s2Zv :: GHC.Prim.State# GHC.Prim.RealWorld) -
case ww_s2Zt of ds_X2F1 {
  __DEFAULT -
case w_s2Zq
of wild_a2Pp { Data.Array.Base.STUArray ds2_a2Pr ds3_a2Ps marr#_a2Pt -
case GHC.Prim.readWord64Array# @ GHC.Prim.RealWorld marr#_a2Pt ds_X2F1
w1_s2Zv
of wild2_a2PA { (# s2#_a2PC, e#_a2PD #) -
(# s2#_a2PC,
   ((case lit_r34C of wild1_a2Ol { GHC.Word.W64# y#_a2On -
 let {
   ww1_a2NY [Just L] :: GHC.Prim.Word#
   [Str: DmdType]
   ww1_a2NY =
 GHC.Prim.xor#
   e#_a2PD
   (GHC.Prim.and#
  (GHC.Prim.uncheckedShiftRL# e#_a2PD 29) __word
6148914691236517205) } in
 let {
   ww2_X2Q0 [Just L] :: GHC.Prim.Word#
   [Str: DmdType]
   ww2_X2Q0 =
 GHC.Prim.xor#
   ww1_a2NY
   (GHC.Prim.and#
  (GHC.Prim.uncheckedShiftL# ww1_a2NY 17) __word
8202884508482404352) } in
 let {
   ww3_X2QE [Just L] :: GHC.Prim.Word#
   [Str: DmdType]
   ww3_X2QE =
 GHC.Prim.xor#
   ww2_X2Q0 (GHC.Prim.and# (GHC.Prim.uncheckedShiftL# ww2_X2Q0 
37)
y#_a2On)
 } in 
   GHC.Word.W64# (GHC.Prim.xor# ww3_X2QE
(GHC.Prim.uncheckedShiftRL# ww3_X2QE 43))
 }),
(GHC.Base.I# (GHC.Prim.+# ds_X2F1 1))) #)
}
};
  312 -
case Mersenne.generateNumbers64 w_s2Zq w1_s2Zv
of wild_a2DL { (# new_s_a2DN, a87_a2DO #) -
case Mersenne.$wnext64 w_s2Zq 0 new_s_a2DN
of wild1_X2Fy { (# new_s1_X2FB, a871_X2FD #) -
case a871_X2FD of wild2_Xar { (w2_aU2, iN_aU3) - (# new_s1_X2FB,
wild2_Xar #) }
}
}
}
end Rec }

Mersenne.next64 :: Data.Array.IO.Internals.IOUArray GHC.Base.Int
GHC.Word.Word64
   - GHC.Base.Int
   - GHC.IOBase.IO (GHC.Word.Word64, GHC.Base.Int)
[GlobalId]
[Arity 3
 Worker Mersenne.$wnext64
 Str: DmdType LU(L)L]
Mersenne.next64 =
  __inline_me (\ (w_s2Zq :: Data.Array.IO.Internals.IOUArray
GHC.Base.Int
 GHC.Word.Word64)
 (w1_s2Zr :: GHC.Base.Int)
 (w2_s2Zv :: GHC.Prim.State# GHC.Prim.RealWorld) -
 case w1_s2Zr of w3_X30R { GHC.Base.I# ww_s2Zt -
 Mersenne.$wnext64 w_s2Zq ww_s2Zt w2_s2Zv
 })





Rec {
Mersenne.$wnext32 :: Data.Array.IO.Internals.IOUArray GHC.Base.Int
  GHC.Word.Word32
 - GHC.Prim.Int#
 - GHC.Prim.State# GHC.Prim.RealWorld
 - (# GHC.Prim.State# GHC.Prim.RealWorld, (GHC.Word.Word32,
GHC.Base.Int) #)
[GlobalId]
[Arity 3
 NoCafRefs
 Str: DmdType LLL]
Mersenne.$wnext32 =
  \ (w_s2YJ :: Data.Array.IO.Internals.IOUArray GHC.Base.Int
GHC.Word.Word32)
(ww_s2YM :: GHC.Prim.Int#)
(w1_s2YO :: GHC.Prim.State# GHC.Prim.RealWorld) -
case ww_s2YM of ds_X2CS {
  __DEFAULT -
case w_s2YJ
of wild_a2Hd { Data.Array.Base.STUArray ds2_a2Hf ds3_a2Hj marr#_a2Hk -
case GHC.Prim.readWord32Array# @ GHC.Prim.RealWorld marr#_a2Hk ds_X2CS
w1_s2YO
of wild2_a2Hr { (# s2#_a2Ht, e#_a2Hu #) -
(# s2#_a2Ht,
   ((let {
   ww1_a2Fr

[Haskell-cafe] How to improve speed? (MersenneTwister is several times slower than C version)

2006-11-01 Thread isto
Hi all,

On HaWiki was an announcement of MersenneTwister made by Lennart
Augustsson.  On a typical run to find out 1000th rnd num the output
is (code shown below):

$ time ./testMTla
Testing Mersenne Twister.
Result is [3063349438]

real0m4.925s
user0m4.856s


I was exercising with the very same algorithm and tried to make it
efficient (by using IOUArray): now a typical run looks like (code shown
below):

$ time ./testMT
Testing Mersenne Twister.
3063349438

real0m3.032s
user0m3.004s


The original C-version (modified so that only the last number is
shown) gives typically

$ time ./mt19937ar
outputs of genrand_int32()
3063349438

real0m0.624s
user0m0.616s

Results are similar with 64 bit IOUArray against 64 bit C variant.
C seems to work about 5 to 10 times faster in this case.

I have tried to do different things but now I'm stuck.  unsafeRead
and unsafeWrite improved a bit the lazy (STUArray-version) and
IOUArray-versions but not very much.  I took a look of Core file but
then, I'm not sure where the boxed values are ok. E.g. should  IOUArray
Int Word64  be replaced with something else?

Any hints and comments on how to improve the efficiency and make
everything better will be appreciated a lot!  

br, Isto

- testMTla.hs (MersenneTwister, see HaWiki)
module Main where

-- ghc -O3 -optc-O3 -optc-ffast-math -fexcess-precision --make testMTla

import MersenneTwister

main = do
putStrLn Testing Mersenne Twister.
let mt = mersenneTwister 100
w = take 1 (drop 999 mt)
-- w = take 1 (drop 99 mt)
putStrLn $ Result is  ++ (show w)
-

- testMT.hs
module Main where

-- Compile eg with
--   ghc -O3 -optc-O3 -optc-ffast-math -fexcess-precision --make testMT

import Mersenne

genRNums32 :: MT32 - Int - IO (MT32)
genRNums32 mt nCnt = gRN mt nCnt 
where gRN :: MT32 - Int - IO (MT32)
  gRN mt nCnt | mt `seq` nCnt `seq` False = undefined
  gRN mt 1= do 
(r,mt') - next32 mt
putStrLn $ (show r)
return mt'
  gRN mt nCnt = do
(r,mt') - next32 mt
gRN mt' $! (nCnt-1) 


main = do
putStrLn Testing Mersenne Twister.
mt32 - initialiseGenerator32 100
genRNums32 mt32 1000
-

- Mersenne.hs (sorry for linewraps)
module Mersenne where

import Data.Bits
import Data.Word
import Data.Array.Base
import Data.Array.MArray
import Data.Array.IO
-- import System.Random


data MT32 = MT32 (IOUArray Int Word32) Int
data MT64 = MT64 (IOUArray Int Word64) Int


last32bitsof :: Word32 - Word32 
last32bitsof a = a .. 0x -- == (2^32-1)  

lm32 = 0x7fff :: Word32
um32 = 0x8000 :: Word32
mA32 = 0x9908b0df :: Word32 -- == 2567483615

-- Array of length 624.
initialiseGenerator32 :: Int - IO MT32 
initialiseGenerator32 seed = do
let s = last32bitsof (fromIntegral seed)::Word32
mt - newArray (0,623) (0::Word32)
unsafeWrite mt 0 s
iG mt s 1
mt' - generateNumbers32 mt
return (MT32 mt' 0)
where
iG :: (IOUArray Int Word32) - Word32 - Int - IO (IOUArray Int
Word32)
iG mt lastNro n  
| n == 624= return mt
| otherwise = do let n1 = lastNro `xor` (shiftR lastNro 
30)
 new = (1812433253 * n1 + 
(fromIntegral n)::Word32) 
 unsafeWrite mt n new
 iG mt new (n+1)


generateNumbers32 :: (IOUArray Int Word32) - IO (IOUArray Int Word32)
generateNumbers32 mt = gLoop 0 mt
where
gLoop :: Int - (IOUArray Int Word32) - IO (IOUArray Int 
Word32)
gLoop i mt 
| i==623  = do 
wL - unsafeRead mt 623
w0 - unsafeRead mt 0
w396 - unsafeRead mt 396
let y = (wL .. um32) .|. (w0 .. lm32) :: 
Word32
if even y 
   then unsafeWrite mt 623 (w396 `xor` (shiftR 
y 1))
   else unsafeWrite mt 623 (w396 `xor` (shiftR 
y 1) `xor` mA32)
return mt
| otherwise = do
wi  - unsafeRead mt i
wi1 - unsafeRead mt (i+1) 
w3  - unsafeRead mt ((i+397) `mod` 624)
let y = (wi .. um32) .|. (wi1 .. lm32)
if even y 
   then unsafeWrite mt i (w3 `xor` (shiftR y 1

Re: [Haskell-cafe] How to improve speed? (MersenneTwister is several times slower than C version)

2006-11-01 Thread isto
Hi, 

When writing IO version, I wasn't aware of other twister versions,
and the only reason is/was that it was easiest to me and that I knew
(believed) that plain lists would have been inefficient.  I just wanted
to see and learn, how close to C version this can be made.  (And still
do.)

There were some good suggestions on this thread - next I'll try 
to get grasp on how to apply the suggestions and do something...

br, Isto

ke, 2006-11-01 kello 22:04 -0500, Lennart Augustsson kirjoitti:
 The whole point of writing the Mersenne Twister was that I wanted to  
 show how a stateful computation could be encapsulated in the ST monad  
 and none of it showing up outside.  This aspect of the code is  
 totally gone now when everything is in the IO monad.  Is there some  
 good reason to have it in the IO monad?
 


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