Re: [Haskell-cafe] State Monad

2004-03-04 Thread Georg Martius
Hi, thanks for your suggestion. The thing is, that I don't want to change the type of my transformation functions. To answer Iavor's question: I have basically two types of transformation functions. One StringTransformation (String -> String) and one transformation with a string and something

[Haskell-cafe] Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread David Sankel
Hello Enthusiasts, My fiancee was assigned the n-queens problem in her Data Structures class. It was a study in backtracking. For those unfamiliar with the problem: one is given a grid of n x n. Return a grid with n queens on it where no queen can be attacked by another. Anyway, I decided

RE: [Haskell-cafe] Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread Michael Wang
Try this Queens.hs module Main where main = print $ queens 10 boardSize = 10 queens 0 = [[]] queens n = [ x : y | y <- queens (n-1), x <- [1..boardSize], safe x y 1] where safe x [] n = True safe x (c:y) n = and [ x /= c , x /= c + n , x /= c - n , safe x y (n+1)] Copi

[Haskell-cafe] Re: Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread Hampus Ram
On Thu, Mar 04 2004, David Sankel wrote: > The Haskell version takes significantly longer (and it gets worse for > larger inputs). So it seems that imperative algorithms are much better for > certain problems. I say this is a case of bad code. Of course language is faster and better if you wri

Re: [Haskell-cafe] Re: Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread ajb
G'day all. Quoting Hampus Ram <[EMAIL PROTECTED]>: > I say this is a case of bad code. Of course language is faster and > better if you write horribly bad code in language . Good link from LtU: http://www.deftcode.com/archives/every_language_war_ever.html Any direct literal translatio

RE: [Haskell-cafe] Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread David Sankel
--- Michael Wang <[EMAIL PROTECTED]> wrote: > Try this Queens.hs Thanks for the program, but how does one decipher the output? David ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Fun with Haskell, runST, MArray, and a few queens. (Imperative Haskell Version)

2004-03-04 Thread David Sankel
> I say this is a case of bad code. Of course language is faster and > better if you write horribly bad code in language . > Taking the first solution found by searching with google I get times > around 0.015s (real) for the Haskell version and 1.7s for your Java > solution (which also seems to b

RE: [Haskell-cafe] Fun with Haskell, runST, MArray, and a few queens.

2004-03-04 Thread Glynn Clements
David Sankel wrote: > > Try this Queens.hs > > Thanks for the program, but how does one decipher the output? The Nth item in each list is the column of the queen which is in row N (or the row of the queen which is in column N; the transpose of a valid solution must also be a valid solution). I