Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread manu
Daniel Fischer's modifications to my original program lead to a 400 %  
speed boost !!!

(It now runs in 22 seconds on my machine)
He avoided unecessary calls to 'length', uses Array instead of Map,  
refactored 'search' function (details below)


I've put up his version on hpaste : http://hpaste.org/2452#a1

Manu



On Aug 26, 2007, at 10:56 PM, Daniel Fischer wrote:

Without much thinking I can spped it up by a factor of 4 (from 280s  
to 60s).

The most important things are:
- don't use length unless you need it
instead of
newV2 - case length newCell of
0 - Nothing
...
and
case length dPlaces of
0 - ...
use
case newCell of
[] - Nothing
[d'] - ...
and
case dPlaces of
[] - Nothing
[s'] - ...

- let dPlaces = [ s' | u - lookup s units, s' - u, elem d (lookup  
s' newV2)]

is bad
let dPlaces = [s' | s' - lookup s peers, elem d (lookup s' newV2)]
scans each peer only once

- search is really bad, you lookup all squares several times,  
potentially

compute all lengths multiple times...
much better is

search :: Grid - Maybe Grid
search g = case [(l,a) | a@(_,xs) - M.assocs g, let l = length xs,  
l /= 1] of

[] - return g
ls - do let (_,(s,ds)) = minimum ls
 msum [assign g (s,d) = search | d - ds]

(I also changed the type, and instead of foldl' you should use  
foldr, since
some is lazy in the second argument, further, since Maybe is a  
MonadPlus,

it's mplus and 'foldr mplus Nothing' is msum)

- Maps aren't good here, too slow lookup and you know the keys, so  
use arrays




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


Re: [Haskell-cafe] Ideas

2007-08-27 Thread luc.taesch

All went finally fine. wiki is live.
thanks for your help. great example. this helped me progressing my
understanding of happs. 

This should conveniently go on the happs tutorial wiki., or at least be
referred to .

(I have seen alex is doing some tutorial on a wiki in the latest head
release, so definitively this is the topic of the day !!)

fyi, the cabal run (runghc) could not find the Diff file ( in the same
directory anyway) o_o
but ghc --make PanDocwiki.hs had it ok.)


John MacFarlane wrote:
 
 lcs can be found at http://urchin.earth.li/darcs/igloo/lcs/
 
 +++ Luc TAESCH [Aug 26 07 23:45 ]:
 when building , i cannot find the lcs mentionned in the cabal file not
 on hasckage nor on goggle.
 could you help?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/Ideas-tf4327747.html#a12344039
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread Jon Harrop
On Monday 27 August 2007 09:09:17 manu wrote:
 Daniel Fischer's modifications to my original program lead to a 400 %
 speed boost !!!
 (It now runs in 22 seconds on my machine)
 He avoided unecessary calls to 'length', uses Array instead of Map,
 refactored 'search' function (details below)

 I've put up his version on hpaste : http://hpaste.org/2452#a1

You shouldn't have any problem writing a purely functional solver that is 
faster and much shorter than Norvig's Python without having to use arrays.

The following purely functional OCaml solver is faster than Norvig's, for 
example, and uses lists, tuples and maps:

open List

let invalid (i, j) (i', j') = i=i' || j=j' || i/3=i'/3  j/3=j'/3

let select p n p' ns = if invalid p p' then filter (() n) ns else ns

let cmp (_, l1) (_, l2) = compare (length l1) (length l2)

let add p n sols =
  sort cmp (map (fun (p', ns) - p', select p n p' ns) sols)

module Map = Map.Make(struct
type t = int * int
let compare = compare
  end)

let rec search f sol = function
  | [] - f sol
  | (p, ns)::sols -
  iter (fun n - search f (Map.add p n sol) (add p n sols)) ns

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
OCaml for Scientists
http://www.ffconsultancy.com/products/ocaml_for_scientists/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread Daniel Fischer
Am Montag, 27. August 2007 14:40 schrieb Jon Harrop:

  Probably not, but what's wrong with using arrays (here and in general)?
  Here I find arrays very natural, after all a grid has a fixed set of
  indices. And as they have a much faster lookup than maps (not to mention
  lists), what do you gain by avoiding them?

 Elegance, brevity and (for short implementations) performance. Although
 this algorithm certainly involves getting and setting puzzle entries from a
 square array, there is little benefit in constraining your solver to
 reflect that explicitly in its concrete data structures.

I'm not convinced (yet).
Elegance: well, yes in general; if you don't know the size of the problem in 
advance certainly. But here?

Brevity: okay, Map.fromList is shorter than array ((0,0),(8,8)), but not 
awfully much so, and you write grid!s regardless of whether grid is a Map 
or an array. So without further elaboration I remain unconvinced of that 
point.

Performance: in my experience arrays are usually much faster (if the algorithm 
is suited to using them, if not, it's a different story, of course).

 Compilers like GHC will be extremely good at performing low-level
 optimizations on list-intensive algorithms. So the performance overhead of
 using lists rather than arrays in a functional language will be small.

That VERY MUCH depends.
I usually use lists for the Project Euler problems first (1. I love lists, 2. 
list code is often far more natural - and hence more elegant) and sometimes 
afterwards re-code it using arrays (boxed arrays or ST(U)Arrays).
More often than not that reduces run time by orders of magnitude(factors 
between 10 and 100 are common, larger or smaller factors occur).
I doubt it's just that my array code is better suited for GHC's optimiser than 
my list code.
Maps I found to perform in between and they are rather memory-hungry.


 Externally, using lists makes it easier to pluck out one choice and the
 remaining choices when searching. That is, after all, the core of this
 algorithm.

Just to make it clear, you are here talking about the list of possibilities 
for some square? Or are you talking about using a list of 
(square, list of possibilites) pairs?

If the former: I represent the grid as an Array (Char,Char) [Char], replacing 
the original representation as a Map String [Char], so I keep that.
Although, in my own solver I keep the set of possibilities for each square as 
an EnumSet (now Data.Set.Enum in the collections package, maybe I should 
update my code), that gains a factor of 2 over lists for the good old 9x9 
grids, more than 10 for 16x16 grids, I fear trying 25x25 grids.
However, I use deduction strategies that involve forming unions and 
differences of several sets of possibilities, operations which are weak spots 
of lists.


   The following purely functional OCaml solver is faster than Norvig's,
   for example, and uses lists, tuples and maps:
 
  snip
  Since I don't speak OCaml, could you translate it to haskell?

 I don't speak Haskell yet but I can translate it into English:

 A puzzle is represented by an association list that maps each coordinate
 onto its possible solutions. Initially, coordinates set in the puzzle map
 onto singleton lists (e.g. ((3, 4), [7]) means position 3,4 in the solution
 must contain 7) and unset coordinates map onto [1..9].

 To search for a solution, you accumulate the solution in another
 association list (e.g. ((3, 4), 7) means that 3,4 contains 7 in the
 solution). You take the coordinate with the shortest list of possibilities
 first and the list of remaining coordinates. You try each of the
 possibilities listed in turn, pushing that choice onto the current solution
 and filtering out all invalidated solutions from the remaining list before
 recursing.

 That's it. Choosing the shortest list first corresponds to constraint
 propagation.

Thought it was something like that.
Must check whether that beats Norvig's constraint propagation.

Cheers,
Daniel

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


[Haskell-cafe] Newbie terminology for partial application

2007-08-27 Thread Peter Verswyvelen
A while ago I confused currying with partial application, which was 
pointed out by members of this community, and the wiki pages got adapted 
so that newbies like me don't make the same mistake twice ;) That's great.


Anyway, at the risk of making mistakes again, I'm looking for good 
terminilogy when talking about partial application.


For example:

-- uncurried form
*f (x,y)*  = -- whatever

-- curried form
*g x y *= f (x,y)

-- partial application
*h x *= g x

But when writing text documents, I guess it is common to say /g is 
curried/, but is it also common to say /g is partially applied? /The 
latter sounds silly to a non-native speaker like myself... Or shouldn't 
it be?

/
/And what is application? I guess it means that (g x y) is internally 
translated to ((g $ x) $ y) which is translated into (apply (apply g x) 
y) where apply is a primitive function?


Thanks,
Peter

PS: sorry for the poor English!

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


[Haskell-cafe] quoting in Haskell

2007-08-27 Thread Peter Verswyvelen
In Scheme, on can quote code, so that it becomes data. Microsoft's F# 
and C# 3.0 also have something similar that turns code into expression 
trees. The latter is used extensively in LINQ which translates plain C# 
code into SQL code or any other code at runtime (this idea came from FP 
I heared)


I can't find something similar for Haskell? Maybe I am looking at the 
wrong places?


In Haskell, I know one can use a data constructor as a function (as in 
(map Just [1..3])), but a function cannot be turned into a data 
constructor (= quoting), can it?


Now this is all really fuzzy for a newbie like me, because aren't all 
functions initially just data constructors waiting to be evaluated in a 
lazy language?


I'm actually looking for something like (loose terminilogy follows) 
context-based-semi-quoting. The idea is to only quote a set of 
functions, while evaluating all the others.


For example, in the code

1 `add` 2 `mul` 3
where
   add = (+)
   mul = (*)

I want to write something like

selectiveQuote [add] (1 `add` 2 `mul` 3)

which would result in an expression tree like

  add
 /  \
16

So the `mul` is not quoted because it is not part of the context = [add]

Maybe this is just impossible, I did not dig deep into this.

Thanks,
Peter

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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread Chaddaï Fouché
For the translation of the above OCaml code, there is not much to do,
in fact it is mostly functional, and so easily translated in Haskell
code, note that I add a code to handle input of the form
4.8.5.3..7..2.6.8.4..1...6.3.7.5..2.1.4..,
to resolve it and print a solution :

haskell
import Data.Ix
import Data.List
import Data.Char
import qualified Data.Map as M

invalid :: (Int, Int) - (Int, Int) - Bool
invalid (i, j) (i', j') = i==i' || j==j' ||
  (i `div` 3 == i' `div` 3  j `div` 3 == j' `div` 3)

select p n p' ns = if invalid p p' then filter (/= n) ns else ns

cmp (_, l1) (_, l2) = (length l1) `compare` (length l2)

add p n sols =
 sortBy cmp $ map (\(p', ns) - (p', select p n p' ns)) sols

search f sol [] = f sol
search f sol ((p, ns):sols) =
 concatMap (\n - search f (M.insert p n sol) (add p n sols)) ns
/haskell




My additions :
haskell
base :: [((Int, Int),[Int])]
base = [((i,j), [1..9]) | i - [0..8], j - [0..8]]

createBoard input = foldr constraint (M.empty, purge base input) input
where
  constraint (p, [n]) (sol,sols) = (M.insert p n sol,add p n sols)
  purge b i = filter (maybe True (const False) . flip lookup i . fst) b

inputBoard :: String - [((Int, Int), [Int])]
inputBoard = filter (not . null . snd)
 . zip (range ((0,0),(8,8)))
. map (\c - if isDigit c then [read [c]] else [])

showSol = unlines . concat .  intersperse ([replicate 15 '-']) . split 3
  . map (unwords . intersperse | . split 3) . split 9
  . map (chr . (+ ord '0')) . M.elems
where
  split n = takeWhile (not . null) . unfoldr (Just . splitAt n)

solve = head . uncurry (search ((:[]).showSol)) . createBoard . inputBoard

main = interact $ solve
/haskell

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


Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Bas van Dijk
On 8/27/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:
 In Scheme, on can quote code, so that it becomes data. Microsoft's F#
 and C# 3.0 also have something similar that turns code into expression
 trees. The latter is used extensively in LINQ which translates plain C#
 code into SQL code or any other code at runtime (this idea came from FP
 I heared)

 I can't find something similar for Haskell? Maybe I am looking at the
 wrong places?

 In Haskell, I know one can use a data constructor as a function (as in
 (map Just [1..3])), but a function cannot be turned into a data
 constructor (= quoting), can it?

 Now this is all really fuzzy for a newbie like me, because aren't all
 functions initially just data constructors waiting to be evaluated in a
 lazy language?

 I'm actually looking for something like (loose terminilogy follows)
 context-based-semi-quoting. The idea is to only quote a set of
 functions, while evaluating all the others.

 For example, in the code

 1 `add` 2 `mul` 3
 where
 add = (+)
 mul = (*)

 I want to write something like

 selectiveQuote [add] (1 `add` 2 `mul` 3)

 which would result in an expression tree like

add
   /  \
 16

 So the `mul` is not quoted because it is not part of the context = [add]

 Maybe this is just impossible, I did not dig deep into this.

 Thanks,
 Peter

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


Look at Template Haskell.

quote from http://haskell.org/th :
Intuitively Template Haskell provides new language features that
allow us to convert back and forth between concrete syntax, i.e. what
you would type when you write normal Haskell code, and abstract syntax
trees. These abstract syntax trees are represented using Haskell
datatypes and, at compile time, they can be manipulated by Haskell
code. This allows you to reify (convert from concrete syntax to an
abstract syntax tree) some code, transform it and splice it back in
(convert back again), or even to produce completely new code and
splice that in, while the compiler is compiling your module.

However I don't know if your 'selectiveQuote' is possible using TH.

regards,

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


Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Peter Verswyvelen

Look at Template Haskell.
Intuitively Template Haskell provides new language features that
allow us to convert back and forth between concrete syntax, i.e. what


Gee coming from C++ that was the last thing I expected templates to do. It 
seems a bit more powerful in Haskell though!

I'll look into that!

Thanks,
Peter


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


[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-27 Thread Gleb Alexeyev

Bryan O'Sullivan wrote:

I just posted a library named suffixtree to Hackage.

http://www.serpentine.com/software/suffixtree/

It implements Giegerich and Kurtz's lazy construction algorithm, with a 
few tweaks for better performance and resource usage.


API docs:

http://darcs.serpentine.com/suffixtree/dist/doc/html/Data-SuffixTree.html

I've tested it on multi-megabyte input strings.


I think I found a bug:
import qualified Data.SuffixTree as T

 T.countRepeats ab (T.construct abab)
1

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


[Haskell-cafe] Re: Newbie terminology for partial application

2007-08-27 Thread Jon Fairbairn
Peter Verswyvelen [EMAIL PROTECTED] writes:

  A while ago I confused currying with partial
 application, which was pointed out by members of this
 community, and the wiki pages got adapted so that newbies
 like me don't make the same mistake twice ;) That's great.
 
 Anyway, at the risk of making mistakes again, I'm looking
 for good terminilogy when talking about partial
 application.
 
 For example:
 
 -- uncurried form
 *f (x,y)*  = -- whatever
 
 -- curried form
 *g x y *= f (x,y)


 -- partial application
 *h x *= g x

It's only a partial application because g takes more than
one argument; bear that in mind.

 But when writing text documents, I guess it is common to say
 /g is curried/,

Actually, I don't think most haskell programmers would say
anything at all.  Haskellers generally write functions in
curried (because partial application is useful), and use
the function uncurry :: (a - b - c) - (a, b) - c
when an uncurried version is needed.


 but is it also common to say /g is partially applied?
 /The latter sounds silly to a non-native speaker like
 myself... Or shouldn't it be?

Sounds OK to me, though again, I'm not sure I would say it
often.  A partial application is just an application that
returns a function, and this is functional programming, so
it goes without saying!

 /And what is application? I guess it means that (g x y) is
 internally translated to ((g $ x) $ y) which is translated
 into (apply (apply g x) y) where apply is a primitive
 function?

Application is itself the primitive, and the notation for
application is juxtaposition (f x).  It might help to have a
look at lambda-calculus (if you have a strong stomach for
abstraction; if you don't it'd just scare you off).

In lambda-calculus there are only four bits of syntax
(I'll use Haskell syntax):

lambda terms:
abstraction: \ a - T -- where T is a lambda term
application: M N -- where M and N are lambda terms
variable reference: v -- where v is just a name
grouping: (M) -- where M is a lambda term

It's possible to think of Haskell as being based on lambda
calculus. Application in Haskell is the same as application
in lambda calculus, abstraction in Haskell has patterns that
lambda calculus does not. The other two are the same.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Newbie terminology for partial application

2007-08-27 Thread Derek Elkins
On Mon, 2007-08-27 at 16:29 +0200, Peter Verswyvelen wrote:
 A while ago I confused currying with partial application, which was 
 pointed out by members of this community, and the wiki pages got adapted 
 so that newbies like me don't make the same mistake twice ;) That's great.
 
 Anyway, at the risk of making mistakes again, I'm looking for good 
 terminilogy when talking about partial application.
 
 For example:
 
 -- uncurried form
 *f (x,y)*  = -- whatever
 
 -- curried form
 *g x y *= f (x,y)
 
 -- partial application
 *h x *= g x
 
 But when writing text documents, I guess it is common to say /g is 
 curried/, but is it also common to say /g is partially applied? /The 
 latter sounds silly to a non-native speaker like myself... Or shouldn't 
 it be?

g -is- curried, just period, i.e. that is a property of g itself.  g is
partially applied to x in h or (g x) is a partial application, i.e. this
is a property of a particular application.  g is applied to x would also
be fine since there is rarely much value in making a distinction between
application and partial application at the level of programming (in
Haskell at least).  You do seem to have a good grasp on the terminology.

 /And what is application? I guess it means that (g x y) is internally 
 translated to ((g $ x) $ y) which is translated into (apply (apply g x) 
 y) where apply is a primitive function?

Yes, application is what you do when you call a function with
arguments.  The side step through ($) is unnecessary, ($) is nothing
special.

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


Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Derek Elkins
On Mon, 2007-08-27 at 17:56 +0200, Peter Verswyvelen wrote:
  Look at Template Haskell.
  Intuitively Template Haskell provides new language features that
  allow us to convert back and forth between concrete syntax, i.e. what
 
 Gee coming from C++ that was the last thing I expected templates to do. It 
 seems a bit more powerful in Haskell though!
 
 I'll look into that!

They aren't related to templates in C++ at all.  It follows from the
general meaning of the word template (as does C++'s usage).  Really,
it's not all that appropriate a name anyway.  You may also find Liskell
interesting http://liskell.org/

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


Re: [Haskell-cafe] Geometry

2007-08-27 Thread Arie Groeneveld
Steve Schafer wrote:

  x = a - sqrt(a^2 - b^2)

 I don't know offhand if there's a straightforward way to arrive at this
 result without using trigonometry.
Here you go, though with a slightly different result
(same as Joel Koerwer):


a^2=(b^2)/4+(a-x)^2   (Pythagoras)
solving x: --
x(1,2) =  a +/- sqrt (a^2 - b^2/4)   (I)


Did anyone compare the answers?

(I)
aai a b = (x1,x2)
   where x1 = a + sqrt disc
 x2 = a - sqrt disc
 disc = a^2-b^2/4

Others:
   
schafer a b = a - sqrt(a^2 - b^2)

jedaï a b = a * (1 - cos (b/(2*a)))


stefan a b = a - a * sqrt (1 - b*b / a*a)

joel a b = a - sqrt (a*a - b*b/4)


Assume a and b are given: a=10; b=8

Results:

*Main aai 10 8
(19.165151389911678,0.8348486100883203)
the answer is the smaller value
the other value =
the diameter of the circumference minus x

(0.00 secs, 523308 bytes)

*Main schafer 10 8
4.0
(0.01 secs, 524924 bytes)

*Main jedaï 10 8
0.789390059971149
(0.01 secs, 524896 bytes)


*Main stefan 10 8
NaN
(0.00 secs, 524896 bytes)

*Main stefan 10 8
4.0
(0.01 secs, 524896 bytes)

*Main joel 10 8
0.8348486100883203
(0.01 secs, 524896 bytes)


Where do I go wrong (I)?


Thanks


@@i

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


Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Bas van Dijk
On 8/27/07, Derek Elkins [EMAIL PROTECTED] wrote:
 ...Really, it's not all that appropriate a name anyway...

Indeed, Meta Haskell would be better I think.

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


Re: [Haskell-cafe] Geometry

2007-08-27 Thread Arie Groeneveld
Correction


 stefan a b = a - a * sqrt (1 - b*b / a*a)

should be:

stefan a b = a - a * sqrt (1 - b*b / (a*a))



 *Main stefan 10 8
 4.0
 (0.01 secs, 524896 bytes)

Thanks


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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread manu

From: Daniel Fischer
 Thought it was something like that.
 Must check whether that beats Norvig's constraint propagation.

it does !

on my machine :

Jon Harrop's : 12.5 sec  and Norvig's : 15 sec


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


Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Dan Piponi
On 8/27/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:
  Look at Template Haskell.
 Gee coming from C++ that was the last thing I expected templates to do. It 
 seems a bit more powerful in Haskell though!

There's much in common between C++ template metaprogramming and
template Haskell - they both allow compile-time computation. On the
question of which is more 'powerful', check out the side by side
comparison here:
http://www.cs.rice.edu/~taha/publications/journal/dspg04b.pdf
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-27 Thread ChrisK
Gleb Alexeyev wrote:
 Bryan O'Sullivan wrote:
 I just posted a library named suffixtree to Hackage.

 http://www.serpentine.com/software/suffixtree/

 It implements Giegerich and Kurtz's lazy construction algorithm, with
 a few tweaks for better performance and resource usage.

 API docs:

 http://darcs.serpentine.com/suffixtree/dist/doc/html/Data-SuffixTree.html

 I've tested it on multi-megabyte input strings.

 I think I found a bug:
 import qualified Data.SuffixTree as T
 
 T.countRepeats ab (T.construct abab)
 1


That is almost certainly because the algorithm expects the source string to have
a unique character at its end.

The library should either make that clear or add such a character on its own.

Otherwise the ab suffix is a prefix of the abab suffix and the shorter one
gets lost.  If you end in $ then ab$ cannot merge with abab$ and there are
no distinct suffixes a and b for which (isPrefixOf a b) is true.

Example:

 *Data.SuffixTree countRepeats ab (construct abab)
 1
 *Data.SuffixTree countRepeats ab (construct abab$)
 2

-- 
Chris

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


Re: [Haskell-cafe] Geometry

2007-08-27 Thread Steve Schafer
On Mon, 27 Aug 2007 19:05:06 +0200, you wrote:

Where do I go wrong (I)?

b is defined to be _half_ of the chord (the semichord, I suppose).
You're assuming it to be the entire chord.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [ANN] pcap 0.3.1, for user-level network packet capture

2007-08-27 Thread Bryan O'Sullivan
I've taken over maintenance of the pcap library (an interface to 
libpcap, for user-level network packet capture), and released a new version.


Home page: http://www.serpentine.com/software/pcap/
API docs: http://darcs.serpentine.com/pcap/dist/doc/html/pcap/
Download: http://hackage.haskell.org/packages/archive/pcap/

darcs repo: darcs get http://darcs.serpentine.com/pcap/

Thanks are due to Gregory Wright for originally writing the package, and 
Dominic Steinitz and Nick Burlett for their respective maintenance efforts.


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


[Haskell-cafe] Re: [ANN] An efficient lazy suffix tree library

2007-08-27 Thread Bryan O'Sullivan

ChrisK wrote:


That is almost certainly because the algorithm expects the source string to have
a unique character at its end.


Chris is correct.  I'll ensure that the docs make this clear.

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


Re: [Haskell-cafe] Geometry

2007-08-27 Thread Chaddaï Fouché
2007/8/27, Steve Schafer [EMAIL PROTECTED]:

 b is defined to be _half_ of the chord (the semichord, I suppose).
 You're assuming it to be the entire chord.


Based on the drawing I thought it was the length of the arc (in blue) ?

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


[Haskell-cafe] Re: quoting in Haskell

2007-08-27 Thread Rene de Visser
Peter Verswyvelen [EMAIL PROTECTED] schrieb im Newsbeitrag 
news:[EMAIL PROTECTED]
 In Scheme, on can quote code, so that it becomes data. Microsoft's F# 
 and C# 3.0 also have something similar that turns code into expression 
 trees. The latter is used extensively in LINQ which translates plain C# 
 code into SQL code or any other code at runtime (this idea came from FP I 
 heared)

The normal way of doing such things in Haskell is to have
1) functions that generate the component data structures (these functions 
are often called smart constructors)
2) other functions to put the functions/data structures together (these 
other functions are often call combinators).

The resulting data structure that represents the sql query for example is 
then processed to produce the real (textual) sql query which this then sent 
to the database.

 I can't find something similar for Haskell? Maybe I am looking at the 
 wrong places?

HaskellDB for example does this for database queries.
Parsec does this parsers.
HSXML (if I got the name right) does this for XML.

 In Haskell, I know one can use a data constructor as a function (as in 
 (map Just [1..3])), but a function cannot be turned into a data 
 constructor (= quoting), can it?
A data constructor is a special case of a function, or perhaps better said, 
a particular way a function is defined. Either a function is a data 
constructor or it isn't.

For example you can also do

just = Just

Just is a data constuctor. It was defined with a data statement (and as a 
result starts with a capital letter).
data Maybe a = Nothing | Just a

just is not a data constructor. Why? It wasn't defined with a data 
statement.

However just and Just behave almost identically. (you can't pattern match on 
just, only on Just)

Rene. 



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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-27 Thread Daniel Fischer
Am Montag, 27. August 2007 10:09 schrieb manu:
 Daniel Fischer's modifications to my original program lead to a 400 %
 speed boost !!!
 (It now runs in 22 seconds on my machine)
 He avoided unecessary calls to 'length', uses Array instead of Map,
 refactored 'search' function (details below)


Ouch! I should've looked at the code more closely. 
That had a bug which resulted in LOTS of futile work.
Fixed that and the Array version now runs in 3 seconds on my computer 
(previous version took 60), the corresponding Map version runs in 7.

What was the saying, 'The best optimisation is a better algorithm'?

Code below.

Cheers,
Daniel

{-

This is an attempt to implement in Haskell, Peter Norvig's sudoku
solver :
Solving Every Sudoku Puzzle (http://norvig.com/sudoku.html)

In Norvig's program, methods which change a grid return either a new
grid, either False (failure).
Here I use Maybe, and return Just grid or Nothing in case of failure

-}

module Main where

import Data.List hiding (lookup)
import Data.Array
import Control.Monad
import Data.Maybe

--
-- Types
type Digit  = Char
type Square = (Char,Char)
type Unit   = [Square]

-- We represent our grid as an array
type Grid = Array Square [Digit]


--
-- Setting Up the Problem

rows = ABCDEFGHI
cols = 123456789
digits = 123456789
box = (('A','1'),('I','9'))

cross :: String - String - [Square]
cross rows cols = [ (r,c) | r - rows, c - cols ]

squares :: [Square]
squares = cross rows cols  -- [('A','1'),('A','2'),('A','3'),...]

peers :: Array Square [Square]
peers = array box [(s, set (units!s)) | s - squares ]
  where
set = nub . concat

unitlist :: [Unit]
unitlist = [ cross rows [c] | c - cols ] ++
[ cross [r] cols | r - rows ] ++
[ cross rs cs | rs - [ABC,DEF,GHI], cs - 
[123,456,789]]

-- this could still be done more efficiently, but what the heck...
units :: Array Square [Unit]
units = array box [(s, [filter (/= s) u | u - unitlist, elem s u ]) | s - 
squares]


allPossibilities :: Grid
allPossibilities = array box [ (s,digits) | s - squares ]

--
-- Parsing a grid into a Map

parsegrid :: String - Maybe Grid
parsegrid g= do regularGrid g
foldM assign allPossibilities (zip squares g)

   where  regularGrid   :: String - Maybe String
  regularGrid g  = if all (\c - (elem c 0.-123456789)) g
  then (Just g)
  else Nothing

--
-- Propagating Constraints

assign:: Grid - (Square, Digit) - Maybe Grid
assign g (s,d) = if (elem d digits)
  then do -- check that we are assigning a digit and not a '.'
let ds = g!s
toDump = delete d ds
foldM eliminate g (zip (repeat s) toDump)
  else return g

eliminate ::  Grid - (Square, Digit) - Maybe Grid
eliminate g (s,d) = let cell = g!s in
 if not (elem d cell) then return g -- already eliminated
 -- else d is deleted from s' values
else do let newCell = delete d cell
newV = g // [(s,newCell)]
newV2 - case newCell of
-- contradiction : Nothing 
terminates the computation
[] - Nothing
-- if there is only one value (d') 
left in square, remove it from peers
[d'] - do let peersOfS = peers!s
   foldM eliminate newV 
(zip peersOfS (repeat d'))
-- else : return the new grid
_ - return newV
-- Now check the places where d appears in the 
units of s
foldM (locate d) newV2 (units ! s)

locate :: Digit - Grid - Unit - Maybe Grid
locate d g u = case filter (elem d . (g !)) u of
[]  - Nothing
[s] - assign g (s,d)
_   - return g

--
-- Search

search :: Grid - Maybe Grid
search g = case [(l,(s,xs)) | (s,xs) - assocs g, let l = length xs, l /= 1] 
of
[] - return g
ls - do let (_,(s,ds)) = minimum ls
 msum [assign g (s,d) = search | d - ds]

solve :: String - Maybe Grid
solve str = do
grd - parsegrid str
search grd

--
-- Display solved grid

printGrid :: Grid - IO ()
printGrid = putStrLn . gridToString

gridToString :: Grid - String
gridToString g = let l0 = elems g
 l1 = (map (\s -   ++ s ++  )) l0

Re: [Haskell-cafe] quoting in Haskell

2007-08-27 Thread Jeremy Shaw
At Mon, 27 Aug 2007 17:04:17 +0200,
Peter Verswyvelen wrote:
 
 In Scheme, on can quote code, so that it becomes data. Microsoft's F# 
 and C# 3.0 also have something similar that turns code into expression 
 trees. The latter is used extensively in LINQ which translates plain C# 
 code into SQL code or any other code at runtime (this idea came from FP 
 I heared)

Depending on what you are trying to do, you might also be able to use
some of the DSL techniques that Lennart Augustsson has been exploring
in his blog over the past couple months.

This is probably a good starting point:

http://augustss.blogspot.com/2007_06_01_archive.html

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


Re: [Haskell-cafe] Geometry

2007-08-27 Thread Peter Verswyvelen




The author of the question (Tony Morris) actually asked two different
questions, and so people gave two different replies :)

To quote Tony:
"I may have misunderstood his problem (we were drawing in dirt) and actually, it is
the straight line between the two points on the circumference that are
known and not the specified 'b', but I figure I could derive one
solution from another if I have misunderstood him."

So, the solution to the drawing, where a is the radius and b is the arc:

x = a * (1 - cos(b/2a)) (because cosine = adjacent / hypotenuse)

The solution to the textual question, where a is the radius and b is the distance between the two points on the circumference:

(a-x)2 + (b/2)2  = a2  

= x2 - 2ax + a2 + (b/2)2 = a2
= x2 - 2ax + (b/2)2 = 0
= x = a  sqrt(4a2 - b2) / 2 (solution to quadratic)
= x = a - sqrt(a2 - b2/4) (move /2 into sqrt, and can't be +sqrt because that would make x greater than a)

So in Haskell

sol1 a b = a * (1 - cos (b / (2*a)))
sol2 a b = a - sqrt (a*a - (b*b)/4)

Cheers,
Peter





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


[Haskell-cafe] No Enum nor Ix instance on Graphics.UI.GLUT.Key

2007-08-27 Thread Peter Verswyvelen
I want to make an array using GLUT.Key as an index, but it is not an 
instance of Enum nor Ix


Of course, I can make it an instance myself, but I guess it would be 
easier to do so in the library?


Cheers,
Peter

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