Re: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Chris Kuklewicz
Daniel Fischer wrote:

 But, lo and behold, I  also tried how plai Array fared in comparison to 
 DiffArray and ... reduced the running time to under ten minutes (a little 
 above for the list version), 5% GC time without -AxM, 1.2% with -A8M.
 
 And I thought, DiffArrays were supposed to be fast!

No.  DiffArray's are faster for the usual imperative single threaded usage
pattern.  The haddock documentation explains:

 Diff arrays have an immutable interface, but rely on internal updates in
 place to provide fast functional update operator //.
 
 When the // operator is applied to a diff array, its contents are physically
 updated in place. The old array silently changes its representation without
 changing the visible behavior: it stores a link to the new current array
 along with the difference to be applied to get the old contents.
 
 So if a diff array is used in a single-threaded style, i.e. after //
 application the old version is no longer used, a'!'i takes O(1) time and a //
 d takes O(length d). Accessing elements of older versions gradually becomes
 slower.
 
 Updating an array which is not current makes a physical copy. The resulting
 array is unlinked from the old family. So you can obtain a version which is
 guaranteed to be current and thus have fast element access by a // [].

I assume the usage in a Sudoku solver involves a non-trivial amount of
back-tracking.  So as the solver backs up and goes forward again it ends up
being much more work than having used a plain Array.

And as was pointed out by someone else on this list: to be thread safe the
DiffArray uses MVar's (with locking) instead of IOVars.

But I expect the main problem is that a DiffArray is simply not the right
mutable data structure for the job.

I have had the flu this week, so I did not finish cleaning up my port of Knuth's
mutable dancing links based Sudoku solver.  But it uses a much more lightweight
way to alter a mutable data structure both going forward and backwards while
backtracking.  And I can use STRef's to build it, instead of MVars.


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


Re[2]: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Bulat Ziganshin
Hello Daniel,

Saturday, April 8, 2006, 3:06:03 AM, you wrote:
 And I thought, DiffArrays were supposed to be fast!

1. your arrays are too small (8 elements only)
2. DiffArray use internally MVars. with IORefs they will be a lot
faster



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread Bulat Ziganshin
Hello Daniel,

Saturday, April 8, 2006, 4:21:14 AM, you wrote:

 Unless I overlooked something, I use foldBits only via size (though that's
 used a lot).

size of set? there is much faster method - use a table

[0..255] - number of bits in this number seen as set

then we split Word to the bytes and count total size of set
by adding number of bits set in each byte

foldBits can be made faster (may be) by adding strict annotations:

foldBits :: Bits c = (a - Int - a) - a - c - a
foldbits _ z bs | z `seq` bs `seq` False  = undefined

foldBits' :: Bits c = (a - Int - a) - Int - c - a - a
foldbits' _ i bs z | i `seq` bs `seq` z `seq` False  = undefined

moreover, GHC don't inline recursive functions! so foldbits' is out of
luck and it seems that GHC generates polymorphic version that is of
course very-very slow. what you can do?

1. use SPECIALIZE pragma. this allow to make faster version at least
for typical cases (a=c=Int, for example)

2. use recursion on the internal foldbits' function. may be this will
help to inline and therefore specialize each call to foldbits'. it's
better to ask Simon Marlow about this

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Bulat Ziganshin
Hello Chris,

Saturday, April 8, 2006, 12:21:07 PM, you wrote:

 backtracking.  And I can use STRef's to build it, instead of MVars.

may be it's better to use unboxed arrays/references?



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Positive integers

2006-04-08 Thread Aaron Denney
On 2006-04-02, ihope [EMAIL PROTECTED] wrote:
 On 3/29/06, Aaron Denney [EMAIL PROTECTED] wrote:
 (And yes, we desperately need something like class aliases.)

 You mean like this?

Not quite, I meant something like John Meacham's proposal:
http://repetae.net/john/recent/out/classalias.html

-- 
Aaron Denney
--

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


Re: Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread David F. Place
Thanks Bulat and Robert.  I implemented Bulat's idea as the  
following.  It tests faster than Roberts.  I use Robert's to compute  
the table.  The performance seems satisfactory now.


size :: Set a - Int
size (Set w) = countBits w
where
  countBits w
  | w == 0 = 0
  | otherwise = countBits (w `shiftR` 8) + bitsTable!(w ..  
0xFF)


bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i - [0..255]]

bitcount :: Word - Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .. (x-1))

On Apr 8, 2006, at 1:21 PM, Robert Dockins wrote:


On Apr 8, 2006, at 4:24 AM, Bulat Ziganshin wrote:


Hello Daniel,

Saturday, April 8, 2006, 4:21:14 AM, you wrote:

Unless I overlooked something, I use foldBits only via size  
(though that's

used a lot).


size of set? there is much faster method - use a table

[0..255] - number of bits in this number seen as set


Or:

bitcount :: Word - Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .. (x-1))

-- | /O(1)/. The number of elements in the set.
size :: Set a - Int
size (Set w) = bitcount w



David F. Place
mailto:[EMAIL PROTECTED]

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


Re: Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread David F. Place


On Apr 8, 2006, at 4:24 AM, Bulat Ziganshin wrote:


foldBits can be made faster (may be) by adding strict annotations:

foldBits :: Bits c = (a - Int - a) - a - c - a
foldbits _ z bs | z `seq` bs `seq` False  = undefined

foldBits' :: Bits c = (a - Int - a) - Int - c - a - a
foldbits' _ i bs z | i `seq` bs `seq` z `seq` False  = undefined


Indeed, I had tried this.  It is slower for reasons that are  
mysterious to me.



David F. Place
mailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Proposal for restructuring Number classes

2006-04-08 Thread Serge D. Mechveliani
On Sat, Apr 08, 2006 at 02:39:39PM +0200, Andrew U. Frank wrote:

 there has been discussions on and off indicating problems with the structure
 of the number classes in the prelude. i have found a discussion paper by
 mechveliani but i have not found a concrete proposal on the haskell' list of
 tickets. 
 i hope i can advance the process by making a concrete proposal for
 which i attach Haskell code and a pdf giving the rational. if i have not
 found other contributions, i am sorry. 
 
 i try a conservative structure, which is more conservative than the
 structure we have used here for several years (or mechveliani's proposal).
 It suggests classes for units (Zeros, Ones) and CommGroup (for +, -),
 OrdGroup (for abs and difference), CommRing (for *, sqr), EuclideanRing (for
 gdc, lcm, quot, rem, div...) and Field (for /). I think the proposed
 structure could be a foundation for mathematically strict approaches (like
 mechveliani's) but still be acceptable to 'ordinary users'.
 
 i put this proposal for discussion here and hope for suggestions how it can
 be improved before i put it to haskell'!
 
 andrew frank
 

For a long time, there exist the following documents and programs

* BAL library (implemented, downloadible) 
  -- Basic Algebra Library for Haskell, which was a proposal for a
  new Num-like library.

* A paper  Haskell and computer algebra 
  which describes the idea of BAL.

* A paper  What should be an universal functional language,
  which describes, what are the problems of Haskell as related to
  algebra.

These three items can be downloaded from   www.botik.ru/~mechvel

by clicking at BAL, and at the papers you choose.

The main problem with the  language  can be illustrated by the 
following example.

The domain  Matrix(n, m)  of matrices  n by m  

depends on the ordinary values. These  n, m  can be computed in 
some cycle at run time.
But in Haskell, we need to model a  _domain_  as a  _type_,  
with several  _instances_  for this type. 
And these latter cannot evolve at run time. 
For example the domain  Matrix(3, m)  must have  
MultiplicativeSemigroup  instance 
-- if  m == 3,  
and must not have such instance otherwise. 
And  m  may change at run-time.

This is the reason for why BAL looks so complicated 
-- and why the proposal has been rejected.
(By the way, both these papers have been rejected by the conference 
referrees of the Haskell community and FP community).

I think that without  dependent types  for a Haskell-like language,  
it is impossible to propose any adequate and in the same time plainly 
looking algebraic class system.

-
Serge Mechveliani
[EMAIL PROTECTED]





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


[Haskell-cafe] Re: Proposal for restructuring Number classes

2006-04-08 Thread Aaron Denney
On 2006-04-08, Serge D. Mechveliani [EMAIL PROTECTED] wrote:
 I think that without  dependent types  for a Haskell-like language,  
 it is impossible to propose any adequate and in the same time plainly 
 looking algebraic class system.

Depends on what you count as adequate.  Mostly I don't need
runtime-varying parameters, so, that's not necessary, and the edifice
you've constructed is both overkill and unwieldy.

-- 
Aaron Denney
--

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


[Haskell-cafe] web servers

2006-04-08 Thread Tim Newsham

Hi Everyone,
   I'm new to the list, been on irc a bit.  I'm still learning haskell.
Wanted to say Hi before getting in to things...

I'm interested in real-world programs in haskell, especially ones where 
security and formal methods are important.  I'm looking at web servers 
right now.  I found a copy of Simon Marlow's HWS on haskell.org's cvs 
server.  I know there's a newer plugin version, but I cant find a working 
link to the actual code.  I've been able to get the code to compile after 
a while, but it still has some warnings of deprecated features which I 
havent been able to get rid of (if anyone's interested in helping out, let 
me know).  Anyway, I configured it an ran it and it works, although I have 
noticed two security flaws in it which need fixing.  Is it possible there 
is a newer version with these flaws fixed?


Besides HWS, what other web servers exist?  Does anyone actually use a 
haskell based web server in practice?  Which web server is considered the 
most mature?  stable?  fastest?


I'm trying to decided if I should sink some time into HWS or if I should 
use another server.


Tim Newsham
http://www.lava.net/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Chris Kuklewicz
I have finished my cleanup of the dancing links based solver for Sudoku.

I don't have time to compare performance with the other programs that have been
posted recently, or to do more profiling of my code.

For those who will say It is ugly, imperative, and ugly! please remember this
is a conversion of Knuth's c-code, which depended on five non-trivial goto jumps
because he did not have tail recursion.  And the whole point of the algorithm
are the imperative unlink  relink routines acting on a sparse binary matrix.

This does not use any clever logic, but it does pick the tightest constraint at
every step.  This means if there is only one obvious possibility for a
position/row/column/block then it will immediately act on it.

The literate source file is attached.

[ My clever logic solver may eventually be cleaned up as well. ]

-- 
Chris

 A Sukodku solver by Chris Kuklewicz (haskell (at) list (dot) mightyreason 
(dot) com)

 I compile on a powerbook G4 (Mac OS X, ghc 6.4.2) using
 ghc -optc-O3 -funbox-strict-fields -O2 --make -fglasgow-exts

 This is a translation of Knuth's GDANCE from dance.w / dance.c

 http://www-cs-faculty.stanford.edu/~uno/preprints.html
 http://www-cs-faculty.stanford.edu/~uno/programs.html
 http://en.wikipedia.org/wiki/Dancing_Links

 I have an older verison that uses lazy ST to return the solutions on
 demand, which was more useful when trying to generate new puzzles to
 solve.

 module Main where

 import Prelude hiding (read)
 import Control.Monad
 import Control.Monad.Fix
 import Data.Array.IArray
 import Control.Monad.ST.Strict
 import Data.STRef.Strict
 import Data.Char(intToDigit,digitToInt)
 import Data.List(unfoldr,intersperse)

 new = newSTRef
 {-# INLINE new #-}
 read = readSTRef
 {-# INLINE read #-}
 write = writeSTRef
 {-# INLINE write #-}
 modify = modifySTRef
 {-# INLINE modify #-}

 Data types to prevent mixing different index and value types

 type A = Int
 newtype R = R A deriving (Show,Read,Eq,Ord,Ix,Enum)
 newtype C = C A deriving (Show,Read,Eq,Ord,Ix,Enum)
 newtype V = V A deriving (Show,Read,Eq,Ord,Ix,Enum)
 newtype B = B A deriving (Show,Read,Eq,Ord,Ix,Enum)

 Sudoku also has block constraints, so we want to look up a block
 index in an array:

 lookupBlock :: Array (R,C) B
 lookupBlock = listArray bb [ toBlock ij | ij - range bb ]
 where ra :: Array Int B
   ra = listArray (0,pred (rangeSize b)) [B (fst b) .. B (snd b)]
   toBlock (R i,C j) = ra ! ( (div (index b j) 3)+3*(div (index b i) 
 3) )

 The values for an unknown location is 'u'.
 The bound and range are given by b and rng.  And bb is a 2D bound.

 u = V 0  -- unknown value
 b :: (Int,Int)
 b = (1,9) -- min and max bounds
 rng = enumFromTo (fst b)  (snd b)  -- list from '1' to '9'
 bb = ((R (fst b),C (fst b)),(R (snd b),C (snd b)))

  A Spec can be turned into a parsed array with ease:

 type Hint = ((R,C),V)
 newtype Spec = Spec [Hint] deriving (Eq,Show)

 type PA = Array (R,C) V

 parse :: Spec - PA
 parse (Spec parsed) = let acc old new = new
   in accumArray acc u bb parsed

 The dancing links algorithm depends on a sparse 2D node structure.
 Each column represents a constraint.  Each row represents a Hint.
 The number of possible hints is 9x9x9 = 271

 type (MutInt st)  = (STRef st) Int

 The pointer types:

 type (NodePtr st) = (STRef st) (Node st)
 type (HeadPtr st)  = (STRef st) (Head st)

 The structures is a 2D grid of nodes, with Col's on the top of
 columns and a sparse collection of nodes.  Note that topNode of Head
 is not a strict field.  This is because the topNode needs to refer to
 the Head, and they are both created monadically.

 type HeadName = (Int,Int,Int) -- see below for meaning

 data Head st = Head {headName:: !HeadName
 ,topNode:: (Node st) -- header node for this column
 ,len:: !(MutInt st)  -- number of nodes below this head
 ,next,prev:: !(HeadPtr st)  -- doubly-linked list
 }

 data Node st = Node {getHint:: !Hint
 ,getHead:: !(Head st)  -- head for the column this node 
 is in
 ,up,down,left,right :: !(NodePtr st)  -- two 
 doubly-linked lists
 }

 instance Eq (Head st) where
 a == b = headName a == headName b

 instance Eq (Node st) where
 a == b = up a == up b

 To initialize the structures is a bit tedious.  Knuth's code reads in
 the problem description from a data file and builds the structure
 based on that.  Rather than short strings, I will use HeadName as the
 identifier.
 
 The columns are (0,4,5) for nodes that put some value in Row 4 Col 5
 (1,2,3) for nodes that put Val 3 in Row 2 and some column
 (2,7,4) for nodes that put Val 4 in Col 7 and some row
 (3,1,8) for nodes that put Val 8 in some (row,column) in Block 
1

 The first head is (0,0,0) which is the root.  The non-root head data
 will be put in an array with 

[Haskell-cafe] Rank 2 polymorphism in pattern matching?

2006-04-08 Thread C Rodrigues
This counterintuitive typechecking result came up when I wrote a wrapper 
around runST.  Is there some limitation of HM with respect to type checking 
pattern matching?


data X a b = X (a - a)
run :: forall a. (forall b. X a b) - a - a
-- This definition doesn't pass the typechecker
run (X f) = f
-- But this definition works
run x = (\(X f) - f) x


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


[Haskell-cafe] Re: Rank 2 polymorphism in pattern matching?

2006-04-08 Thread Aaron Denney
On 2006-04-08, C Rodrigues [EMAIL PROTECTED] wrote:
 This counterintuitive typechecking result came up when I wrote a wrapper 
 around runST.  Is there some limitation of HM with respect to type checking 
 pattern matching?

 data X a b = X (a - a)
 run :: forall a. (forall b. X a b) - a - a
 -- This definition doesn't pass the typechecker
 run (X f) = f
 -- But this definition works
 run x = (\(X f) - f) x

Have you tried 
run (X f) x = f x
?


-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Rank 2 polymorphism in pattern matching?

2006-04-08 Thread Bruno Oliveira



Hello,



See this message:



http://article.gmane.org/gmane.comp.lang.haskell.general/13145/



Your (initial) program should work in GHC 6.2. I actually find this feature useful, 

but Simon apparently changed this when moving to GHC 6.4 and nobody complained...

Apparently not many people use this feature.



Cheers,



Bruno



On Sat, 08 Apr 2006 18:31:03 +, C Rodrigues wrote:



This counterintuitive typechecking result came up when I wrote a wrapper 

around runST.  Is there some limitation of HM with respect to type checking 

pattern matching?



data X a b = X (a - a)

run :: forall a. (forall b. X a b) - a - a

-- This definition doesn't pass the typechecker

run (X f) = f

-- But this definition works

run x = (\(X f) - f) x





___

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] lambda evaluator in GADT

2006-04-08 Thread paul
The introduction to GADT usually starts with a little expression
evaluator. So I gave it a try, but there are some troubles. 

A little data type for lambda expression

 data E a where
   Lit :: a - E a
   App :: E (a - b) - E a - E b
   Lam :: Var a - E b - E (a - b)
   Val :: Var a - E a

 data Var a = Var String

some sample values

 e1 = Lit 1
 plus = Lit (\x y - x + y)

Next, plus' demonstrate a pitfall in my data definition,
i.e., the variable introduced by Lam has type forall a . a,
which is is too general force a constraint on its
occurrances. I wonder if there a way to make it work. 

 plus' = let v1 = Var x
 v2 = Var y
  in Lam v1 (Lam v2 (App (App plus (Val v1)) (Val v2)))

evaluation

 eval :: E a - a
 eval (Lit x) = x
 eval (App f x) = (eval f) (eval x)
 eval (Lam (Var v) e) = \x - eval (sub v (Lit x) e)
 eval (Val (Var v)) = undefined

substituation

 sub :: String - E b - E c - E c
 sub v e e1@(Lit x) = e1
 sub v e (App f x) = App (sub v e f) (sub v e x)
 sub v e e'@(Lam w'@(Var w) x) =
   if v == w then e'
  else Lam w' (sub v e x)

the above all works fine, except for the following

 {--
 sub v e e'@(Val (Var w)) =
   if v == w then e
 else e'
 --}

It seems the last case requires a unification 
of b and c, which is simply too strong for other
cases. What should I do here?

Instead of substituting on term level, an alternative
way to implement eval is to use an environment to
map variables to its values, but that requires all
expression values to have a uniform type, which is
a conflict to GADT. I'm sure this could be a common
issue encountered by GADT beginners, how does one
get around it?

One solution on top of my head is to use a sum type
(or even type class) and stuff every possible value
types under it, but that defeats the purpose of 
using GADT in the first place.

Any help is greatly appreciated!

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


Re: Re[2]: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread Robert Dockins


On Apr 8, 2006, at 1:58 PM, David F. Place wrote:

Thanks Bulat and Robert.  I implemented Bulat's idea as the  
following.  It tests faster than Roberts.  I use Robert's to  
compute the table.  The performance seems satisfactory now.


size :: Set a - Int
size (Set w) = countBits w
where
  countBits w
  | w == 0 = 0
  | otherwise = countBits (w `shiftR` 8) + bitsTable!(w ..  
0xFF)


bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i - [0..255]]

bitcount :: Word - Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .. (x-1))


There's a couple of other nice bit-twiddily things you can do:

countBits :: Word - Int
countBits w
   | w == 0 = 0
   | otherwise = countBits (w `shiftR` 8) + bitsTable!(w .. 0xFF)

bitsTable :: Array Word Int
bitsTable = array (0,255) $ [(i,bitcount i) | i - [0..255]]

bitcount :: Word - Int
bitcount 0 = 0
bitcount x = 1 + bitcount (x .. (x-1))

lsb :: Word - Int
lsb x = countBits ((x-1) .. (complement x))

-- stolen from http://aggregate.org/MAGIC/
msb :: Word - Int
msb x0 = let
 x1 = x0 .|. (x0 `shiftR` 1)
 x2 = x1 .|. (x1 `shiftR` 2)
 x3 = x2 .|. (x2 `shiftR` 4)
 x4 = x3 .|. (x3 `shiftR` 8)
 x5 = x4 .|. (x4 `shiftR` 16)
 in countBits x5 - 1


findMinIndex :: Word - Int
findMinIndex 0 =
error EnumSet.findMin: empty set has no minimal element
findMinIndex w = lsb w

findMaxIndex :: Word - Int
findMaxIndex 0 =
error EnumSet.findMax: empty set has no maximal element
findMaxIndex w = msb w



Which should make all access to the greatest or least element O(1).   
I guess, come to think of it, all operations on EnumSet are O(1) by  
virtue of the set size being upper-bounded.  At any rate this turns  
recursion into unboxable straight-line code and I think it does less  
allocations.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Daniel Fischer
Am Samstag, 8. April 2006 02:20 schrieb Daniel Fischer:
 Am Freitag, 7. April 2006 17:33 schrieben Sie:
   Just out of curiosity, speed was not the objective when I wrote my
   solver, I wanted to avoid guesswork (as much as possible), but in
   comparison with Cale Gibbard's and Alson Kemp's solvers (which are much
   more beautifully coded), it turned out that mine is blazingly fast, so
   are there faster solvers around (in Haskell, in other languages)?
 
  if I modify your solver to produce similar output to mine (input/first
  propagation, solved puzzle, number and list of guesses made), your's
  takes about a third of the time of mine (solving 36628 17hint puzzles
  in 6m vs 17m, 2GHz Pentium M), and I wasn't exactly unhappy with
  my solver before I did this comparison!-)

 Mine's even faster now (at least on my computer, would you care to test it
 on your's? If you don't want to get EnumSet, just change DiffArray to
 Array, worked wonders for me), I'll dig into yours tomorrow to see what I
 can get out of it to improve my algorithm.

Unforunately, no new inference rules :-(
Two things I don't like about your code:
1. no type declarations
2. too much name shadowing, that makes following the code difficult

apart from that: clever

  like you, I've been trying to remove guesses, and the speed came as a
  welcome bonus (I'm still using lists all over the place, with lots of not
  nice adhoc code still remaining; not all propagators are iterated fully

 lists and adhoc code tend to be performance killers, I doubled the speed of
 mine by de-adhoccing the code (and that although I introduced the
 speed-killer DiffArray)

I believe if you change the representation of puzzles from [(pos,range)]
to an Array, you'll get a significant speedup

  yet because I only recently removed a logic bug that slowed down the
  search instead of speading it up; ..). so the more interesting bit is
  that our solvers disagree on which are the most difficult puzzles
  (requiring the largest number of guesses):
 
  df
  puzzles involving guesses: 5319

 If that's not a typo, I'm baffled. My original needed to guess in 5309

Rot! Typo in _my_ previous message, 5319 is correct.

 puzzles, and I can't imagine what inference I could have dropped when
 cleaning up the code.

  largest number of guesses:
  10 (#36084), 11 (#22495)
 
  cr
  puzzles involving guesses: 8165
  largest number of guesses:
  10 (#9175), 10 (#17200), 10 (#29823), 10 (#30811)
 
  df's solver needs 0/0/3/0 for cr's trouble spots, while cr's solver needs
  5/9 guesses for df's. lots of potential for interesting investigations,

We use different guessing strategies (plus, I also have group-inference).
But the given number of guesses is the number of guesses in the successful 
branch, and I think a better measure for the nefariousness of a puzzle is the 
accumulated number of guesses in all branches or the number of branches 
(still better is the time needed to solve the puzzle).

This is the list of the 30 puzzles with the most branches:
puzzle  #branches
  3992   213
  7475   120
 12235   117
  534169
 1181560
  940260
 1154459
  918454
 1040350
 3111048
  857548
  148945
  273240
 1152339
  673039
 1092938
   96035
 1947432
  641231
  159930
 3608429
 2183229
 2249528
  465728
 3474727
 1040427
 2993126
   94225
   56324

the top 30 in CPUTime (in milliseconds, cpuTimePrecision = 10^10)
  3992  6480
  9184  1520
 31110  1470
 10403  1310
 12235  1260
  7475  1130
  2732  1080
   960  1050
  5341   990
 11544   960
 11815   930
  1395   730
 10929   710
  1863   710
  1330   700
 20807   630
  4181   610
 10634   570
 34401   550
   959   550
 34747   520
  1599   520
 14912   510
 29282   500
  7983   500
 29273   480
 23958   470
  2245   460
  2232   440
 36425   430

so puzzle 3992 is outstandingly bad in both respects (I fed it into my old 
step by step solver and boy, failure is detected _very_ late in practically 
all branches) and from a couple of tests I have the vague impression that the 
correlation between the number of guesses in the successful branch and time 
is not very strong (3992 has 6, 9184 and 2732 only 3, 31110 has 5, 10403 8, 
12235 9, 7475 6 and 960 7), but I don't think I'll do a statistical analysis, 
I'll stick to time as the measure.

Here's the meanest puzzle:

0 0 0 0 4 0 0 5 9
3 0 0 2 0 0 0 0 0
1 0 0 0 0 0 0 0 0
0 0 0 1 0 0 7 0 0
0 4 6 0 0 0 0 0 0
9 5 0 0 0 0 0 0 0
0 0 0 0 5 6 0 4 0
0 0 0 8 0 0 3 0 0
0 0 0 0 0 0 0 0 0

and that's so mean that David Place's incrsud beats my solver on this by a 
factor of 5.5!

  though mostly for me!-)

 ^^
 I'm not sure about that :-)

  cheers,
  claus

Cheers again,
Daniel

-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton


Re: [Haskell-cafe] Understanding allocation behavior

2006-04-08 Thread Daniel Fischer
Hum,
oddly, these actually slow things down. 
While the new size brought the sudoku17 time from ~570s down to ~490s,
the new findMinIndex/findMaxIndex increased the time to ~515s, although hardly 
used.
Why?

Cheers,
Daniel

Am Sonntag, 9. April 2006 00:54 schrieb Robert Dockins:
 On Apr 8, 2006, at 1:58 PM, David F. Place wrote:
  Thanks Bulat and Robert.  I implemented Bulat's idea as the
  following.  It tests faster than Roberts.  I use Robert's to
  compute the table.  The performance seems satisfactory now.
 
  size :: Set a - Int
  size (Set w) = countBits w
  where
countBits w
 
| w == 0 = 0
| otherwise = countBits (w `shiftR` 8) + bitsTable!(w .. 0xFF)
 
  bitsTable :: Array Word Int
  bitsTable = array (0,255) $ [(i,bitcount i) | i - [0..255]]
 
  bitcount :: Word - Int
  bitcount 0 = 0
  bitcount x = 1 + bitcount (x .. (x-1))

 There's a couple of other nice bit-twiddily things you can do:

 countBits :: Word - Int
 countBits w

 | w == 0 = 0
 | otherwise = countBits (w `shiftR` 8) + bitsTable!(w .. 0xFF)

 bitsTable :: Array Word Int
 bitsTable = array (0,255) $ [(i,bitcount i) | i - [0..255]]

 bitcount :: Word - Int
 bitcount 0 = 0
 bitcount x = 1 + bitcount (x .. (x-1))

 lsb :: Word - Int
 lsb x = countBits ((x-1) .. (complement x))

 -- stolen from http://aggregate.org/MAGIC/
 msb :: Word - Int
 msb x0 = let
   x1 = x0 .|. (x0 `shiftR` 1)
   x2 = x1 .|. (x1 `shiftR` 2)
   x3 = x2 .|. (x2 `shiftR` 4)
   x4 = x3 .|. (x3 `shiftR` 8)
   x5 = x4 .|. (x4 `shiftR` 16)
   in countBits x5 - 1


 findMinIndex :: Word - Int
 findMinIndex 0 =
  error EnumSet.findMin: empty set has no minimal element
 findMinIndex w = lsb w

 findMaxIndex :: Word - Int
 findMaxIndex 0 =
  error EnumSet.findMax: empty set has no maximal element
 findMaxIndex w = msb w



 Which should make all access to the greatest or least element O(1).
 I guess, come to think of it, all operations on EnumSet are O(1) by
 virtue of the set size being upper-bounded.  At any rate this turns
 recursion into unboxable straight-line code and I think it does less
 allocations.



 Rob Dockins

 Speak softly and drive a Sherman tank.
 Laugh hard; it's a long way to the bank.
-- TMBG
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton

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


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-04-08 Thread Daniel Fischer
Am Samstag, 8. April 2006 20:28 schrieb Chris Kuklewicz:
 I have finished my cleanup of the dancing links based solver for Sudoku.

 I don't have time to compare performance with the other programs that have
 been posted recently, or to do more profiling of my code.

Your dancing links:

ckSud +RTS -sstderr -H32M -A8M  sudoku17  Solutions.txt
ckSud +RTS -sstderr -H32M -A8M
62,941,602,892 bytes allocated in the heap
330,404,632 bytes copied during GC
465,944 bytes maximum residency (41 sample(s))

   2023 collections in generation 0 ( 15.60s)
 41 collections in generation 1 (  0.30s)

 32 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time  734.59s  (781.93s elapsed)
  GCtime   15.90s  ( 16.73s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time  750.49s  (798.66s elapsed)

  %GC time   2.1%  (2.1% elapsed)

  Alloc rate85,682,629 bytes per MUT second

  Productivity  97.9% of total user, 92.0% of total elapsed

Without -HxM, -AxM:

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time  597.47s  (915.94s elapsed)
  GCtime  912.65s  (1363.63s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time  1510.12s  (2279.57s elapsed)

My version using EnumSet (with the faster 'size'):

sudokus +RTS -sstderr  Solutions
sudokus +RTS -sstderr
82,190,535,600 bytes allocated in the heap
771,054,072 bytes copied during GC
153,512 bytes maximum residency (394 sample(s))

 286104 collections in generation 0 ( 33.98s)
394 collections in generation 1 (  0.35s)

  2 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time  482.51s  (1105.12s elapsed)
  GCtime   34.33s  ( 79.90s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time  516.84s  (1185.02s elapsed)

  %GC time   6.6%  (6.7% elapsed)

  Alloc rate170,339,548 bytes per MUT second

  Productivity  93.4% of total user, 40.7% of total elapsed

Nice that original Haskell code can beat a translation from C.

However:
setSud ../puzzle3992 +RTS -sstderr
628|743|159
395|261|478
174|589|632
---+---+---
832|195|764
746|328|591
951|674|283
---+---+---
213|956|847
469|817|325
587|432|916
===
888,672,920 bytes allocated in the heap
  3,352,784 bytes copied during GC
 45,648 bytes maximum residency (1 sample(s))

   3287 collections in generation 0 (  0.21s)
  1 collections in generation 1 (  0.00s)

  2 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time4.77s  (  4.77s elapsed)
  GCtime0.21s  (  0.22s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time4.98s  (  4.99s elapsed)

  %GC time   4.2%  (4.4% elapsed)

  Alloc rate186,304,595 bytes per MUT second

  Productivity  95.8% of total user, 95.6% of total elapsed

But
ckSud +RTS -sstderr  oneBad
ckSud +RTS -sstderr
(1,673941852148256379295378461534167928826594713917832546351729684762483195489615237)
(2,683941752179258463245376918534167829826594371917832546351729684762483195498615237)
(3,829143657361785492547629381678954213934271568215836974152468739486397125793512846)
(4,713642958825917436649835127594781362378264519261593784136478295482359671957126843)
(5,763942158425817936189635427594781362378264519216593784631478295842359671957126843)
(6,269743158371865924458921637945137286836492571712658349597386412683214795124579863)
(7,269743158371865924485921637943157286856492371712638549597386412638214795124579863)
(8,628743159395261478174589632832195764746328591951674283213956847469817325587432916)
(9,983541762761328945524679813679483251835162497142957638457816329296735184318294576)
(10,578942361923165748614837925867491532235786194149253876796514283452378619381629457)
(11,938145762127396854654872931873629145546713289291584673415967328369258417782431596)
(12,792548361531672894846931572657384129483129657219756438965817243174263985328495716)
(13,738249561296517483154386927673192854981654372425873619547928136319765248862431795)
(14,957842361386719452124653879598364127673281945412975638845137296231596784769428513)
(15,598241367673958124421736985254873691317692548986415732742169853165384279839527416)
 25,708,036 bytes allocated in the heap
  9,097,220 bytes copied during GC
329,648 bytes maximum residency (5 sample(s))

 97 collections in generation 0 (  0.42s)
  5 collections in generation 1 (  0.04s)

  2 Mb total memory in use

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.23s  (  0.23s elapsed)
  GCtime0.46s  (  0.46s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.69s  (  0.69s elapsed)

  %GC time  66.7%  (66.7% elapsed)

  Alloc rate111,774,069 bytes per MUT second

  Productivity  33.3% of total user, 33.3% of total elapsed

The infamous puzzle 3992 is the eighth in oneBad, so the links dance rings 
around me for that.
I wonder where the dancing links run into difficulties.
I'll see whether I can grok (that does mean 

Re: [Haskell-cafe] web servers

2006-04-08 Thread Jared Updike
I don't know if there's anything newer, but you could check out:

http://happs.org/HAppS/README.html
http://www.informatik.uni-freiburg.de/~thiemann/WASH/

Hope that helps,
  Jared.

On 4/8/06, Tim Newsham [EMAIL PROTECTED] wrote:
 Hi Everyone,
 I'm new to the list, been on irc a bit.  I'm still learning haskell.
 Wanted to say Hi before getting in to things...

 I'm interested in real-world programs in haskell, especially ones where
 security and formal methods are important.  I'm looking at web servers
 right now.  I found a copy of Simon Marlow's HWS on haskell.org's cvs
 server.  I know there's a newer plugin version, but I cant find a working
 link to the actual code.  I've been able to get the code to compile after
 a while, but it still has some warnings of deprecated features which I
 havent been able to get rid of (if anyone's interested in helping out, let
 me know).  Anyway, I configured it an ran it and it works, although I have
 noticed two security flaws in it which need fixing.  Is it possible there
 is a newer version with these flaws fixed?

 Besides HWS, what other web servers exist?  Does anyone actually use a
 haskell based web server in practice?  Which web server is considered the
 most mature?  stable?  fastest?

 I'm trying to decided if I should sink some time into HWS or if I should
 use another server.

 Tim Newsham
 http://www.lava.net/~newsham/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe