Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-18 Thread Lennart Augustsson
I agree.  Computation on the type level does not imply computation on the
value level.

On 8/18/07, Tim Chevalier [EMAIL PROTECTED] wrote:

 On 8/17/07, Kim-Ee Yeoh [EMAIL PROTECTED] wrote:
  Incidentally, GHC's type checker is Turing complete. You
  already have as much static evaluation as is practically possible.
  You already knew that.
 

 I don't see how the first statement implies the second.

 Cheers,
 Tim

 --
 Tim Chevalier * catamorphism.org * Often in error, never in doubt
 It's never too early to start drilling holes in your car.  -- Tom
 Magliozzi
 ___
 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


Re: [Haskell-cafe] Remember the future

2007-08-18 Thread Andrew Coppin

Dan Piponi wrote:

On 8/17/07, Dan Piponi [EMAIL PROTECTED] wrote:
  

On 8/17/07, Andrew Coppin [EMAIL PROTECTED] wrote:


That sounds completely absurd to me... can anybody explain?
  

Except...you can switch on ghc's special time travel features...



On reflection I decided my example isn't very convincing. For one
thing, I've argued in another thread that monads aren't really about
sequencing actions. But I concede that there is an exception: the IO
monad. Because the IO monad has observable side effects you can
actually see whether or not an action has taken place at a particular
time, so it really does have to sequence actions. So now consider the
following code:

  

import IO
import Control.Monad.Fix



  

test = mdo
z - return $ x+y
print Hello
x - readLn
y - readLn
return z



Evaluate test and you'll be prompted to enter a pair of numbers.
You'll then be rewarded with their sum. But the Hello message is
printed before the prompt for input so we know that's being executed
first. And we can see clearly that the summation is performed before
the Hello message. So clearly this program is computing its result
before receiving the input.

At this point your natural reaction should be to replace 'print
Hello' with 'print z'...
  


Surely all this means is that the magical mdo keyword makes the 
compiler arbitrarily reorder the expression...?


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


Re: [Haskell-cafe] Diagnosing stack overflow

2007-08-18 Thread Matthew Brecknell
Justin Bailey:
 Would retainer profiling help me see what was building up
 this large thunk/closure?

I'm not really familiar enough with GHC's profiling to answer that, but
I'll take a guess.

My guess is that profiling will only sometimes be useful in diagnosing
stack overflows, because I suspect that memory stats reported by the
profiler will usually be dominated by heap usage. So profiling *might*
point you towards some big thunks on the heap which might cause a stack
overflow on evaluation. If so, then you're in luck.

But the problem is that you don't actually *need* a huge unevaluated
thunk to cause a stack overflow. Sure, the foldl example had one, but
consider what happens if we use foldr instead:

print (foldr (+) 0 [1..])
= print (1+(foldr (+) 0 [2..]))
= print (1+(2+(foldr (+) 0 [3..])))
= print (1+(2+(3+(foldr (+) 0 [4..]
= ...
= print (1+(2+(3+(...+(foldr (+) 0 [...]
= stack overflow

It's a bit more tricky to explain what's going on here, which may be one
reason why foldr is not the usual stack overflow example. While the
nested additions in the foldl example represented a long chain of
unevaluated thunks on the heap, here they represent partially executed
computations on the stack. There is no big thunk! But there are still
many nested contexts on the stack, so we still get an overflow.

Another way of contrasting the foldl and foldr examples is to realise
that foldl always consumes its entire input list, while foldr only
consumes as much as its asked to. In the former, foldl drives the
process of thunk building. In the latter, it is the evaluation of the
innermost (+) function that drives foldr to generate the next iteration.

I suspect that explanation is not very clear, so I give a small
experiment which will at least show that I'm not lying. :-)

Run a basic GHC profile (without optimisations) on each of the
following, and observe the total memory usage. With foldl, memory usage
is very high, because the entire list is consumed to produce a huge
thunk on the heap. With foldr, memory usage is only about 16M, just
enough to blow the stack.

-- trial 1: stack overflow, lots of memory consumed
main = print (foldl (+) 0 [1..1000] :: Int)

-- trial 2: stack overflow, minimal memory consumption
main = print (foldr (+) 0 [1..1000] :: Int)

In fact, we could give foldr an infinite list, and get exactly the same
result. Curiously, if we give foldl an infinite list, we don't get a
stack overflow, because we never get to the point of evaluating the
thunk. Instead, we get heap exhaustion, because we just keep building
thunks.

-- trial 4: heap exhaustion, nasty
main = print (foldl (+) 0 [1..] :: Int)

-- trial 5: stack overflow, minimal memory consumption
main = print (foldr (+) 0 [1..] :: Int)

It's also instructive to run these tests with optimisations (no
profiling), to see how they are affected by strictness analysis. Note
that strictness analysis doesn't work for the default Integer type, so
the Int type annotations are necessary.

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


[Haskell-cafe] Re: Remember the future

2007-08-18 Thread Benjamin Franksen
Andrew Coppin wrote:
 Surely all this means is that the magical mdo keyword makes the 
 compiler arbitrarily reorder the expression...?

It is not magical but simple syntactic sugar. And no, the compiler does
not 'arbitrarily reorder' anything, you do the same in any imperative
language with pointers/references and mutation.

From the ghc manual:

---
7.3.3. The recursive do-notation
...
 The do-notation of Haskell does not allow recursive bindings, that is, the
variables bound in a do-expression are visible only in the textually
following code block. Compare this to a let-expression, where bound
variables are visible in the entire binding group. It turns out that
several applications can benefit from recursive bindings in the
do-notation, and this extension provides the necessary syntactic support.

Here is a simple (yet contrived) example: 
import Control.Monad.Fix

justOnes = mdo xs - Just (1:xs)
   return xs

 As you can guess justOnes will evaluate to Just [1,1,1, 
 The Control.Monad.Fix library introduces the MonadFix class. It's
definition is: 
class Monad m = MonadFix m where
   mfix :: (a - m a) - m a
---

It is unfortunate that the manual does not give the translation rules, or at
least the translation for the given example. If I understood things
correctly, the example is translated to

justOnes = mfix (\xs' - do { xs - Just (1:xs'); return xs }

You can imagine what happens operationally by thinking of variables as
pointers. As long as you don't de-reference them, you can use such pointers
in expressions and statements even if the object behind them has not yet
been initialized (=is undefined). The question is how the objects are
eventually be initialized. In imperative languages this is done by
mutation. In Haskell you employ lazy evaluation: the art of circular
programming is to use not-yet-defined variables lazily, that is, you must
never demand the object before the mdo block has been executed.

A good example is http://www.cse.ogi.edu/PacSoft/projects/rmb/doubly.html
which explains how to create a doubly linked circular list using mdo.

Cheers
Ben

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


Re: [Haskell-cafe] Remember the future

2007-08-18 Thread Dan Piponi
On 8/18/07, Andrew Coppin [EMAIL PROTECTED] wrote:

 Surely all this means is that the magical mdo keyword makes the
 compiler arbitrarily reorder the expression...?

What mdo actually does is described here:
http://www.cse.ogi.edu/PacSoft/projects/rmb/mdo.pdf

My last example desugars to:

test = mfix (
\ ~(x,y,z,v) - do
z - return $ x+y
print Hello
x - readLn
y - readLn
v - return z
return (x,y,z,v))
= \(x,y,z,v) - return v

So at core there really is a do-expression that's passing 'return $
x+y' into a print which in turn is passed into the 'readLn's.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsing binary data.

2007-08-18 Thread Peter Cai
Hi all,

Recently I am considering doing part of my job using Haskell.

My duty is writing a network server which talks to another server through a
binary based private protocol.

As the old version of this component is written in C, it's very natural that
this protocol is base on C structure definitions, which are, unfortunately,
very complicated.  And the worse is that every field in every structure must
be converted to Network Endian.

As I am a newbie to Haskell, I am not sure how to handle this problem with
less work.  Do you have any ideas about this problem?

Thanks in advance!

-- 
There is No CODE That is More Flexible Than NO Code!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sudoku Solver

2007-08-18 Thread Wouter Swierstra
I'm a little surprised no one's tried a parallel solution yet,  
actually.

We've got an SMP runtime for a reason, people!


I hacked up a parallel version of Richard Bird's function pearl solver:

http://www.haskell.org/sitewiki/images/1/12/SudokuWss.hs

It not really optimized, but there are a few neat tricks there.  
Rather than prune the search space by rows, boxes, and columns  
sequentially, it represents the sudoku grid by a [[TVar [Int]]],  
where every cell has a TVar [Int] corresponding to the list of  
possible integers that would 'fit' in that cell. When the search  
space is pruned, we can fork off separate threads to prune by  
columns, rows, and boxes -- the joy of STM!


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


Re: [Haskell-cafe] Parsing binary data.

2007-08-18 Thread Marc Weber
As I am a newbie to Haskell, I am not sure how to handle this problem
with less work.  Do you have any ideas about this problem?
Thanks in advance!

Have a look at 
http://haskell.org/haskellwiki/Applications_and_libraries/Data_structures
section 3 (IO) - http://haskell.org/haskellwiki/Binary_IO

Of course you can just use most different parser libraries as well, because most
are not tight to one token type.. So you shouldn't have any trouble
parsing a ByeSttring which is a char (8bit word) buffer.

I'd recommend having a look at ParseP or happy/ alex .. if the binary
libraries aren't suited for your task..

But to get the fastest/ whatsoever solution you should wait for
different replies as I haven't used all those yet to parse binary data..

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


[Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Peter Verswyvelen
When reading an article about tail recursion
(http://themechanicalbride.blogspot.com/2007/04/haskell-for-c-3-programmers.
html) I came across the follow statements:

If you can write a non-recursive function that uses the colon syntax it is
probably better than a tail recursive one that doesn't. This is because
Haskell's lazy evaluation enabled you to use the non-tail recursive version
on an infinite stream without getting a stack overflow. 

and

Unfortunately, laziness gets in the way. While transforming
non-tail-recursive code to a tail-recursive form is important and useful for
functional programming in general, dealing with laziness requires a little
more care, and often non-tail-recursive versions are preferrable. flatten
is an example of this, the first version is better in many ways. While I
don't believe it happens in this case, oftentimes naively writing code
tail-recursively in Haskell will actually -make- it overflow the stack.
Another (actual) benefit of the first version of flatten is that it will
work on infinite lists. http://www.haskell.org/hawiki/StackOverflow gives a
simple example and some explanation.

Unfortunately I can't find the StackOverflow page anymore.

Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)

bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo just puts
the delayed computation in the cdr of the list, while lazy evaluation of
bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that? 

Thanks,
Peter










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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Derek Elkins
On Sat, 2007-08-18 at 20:35 +0200, Peter Verswyvelen wrote:
 When reading an article about tail recursion
 (http://themechanicalbride.blogspot.com/2007/04/haskell-for-c-3-programmers.
 html) I came across the follow statements:
 
 If you can write a non-recursive function that uses the colon syntax it is
 probably better than a tail recursive one that doesn't. This is because
 Haskell's lazy evaluation enabled you to use the non-tail recursive version
 on an infinite stream without getting a stack overflow. 
 
 and
 
 Unfortunately, laziness gets in the way. While transforming
 non-tail-recursive code to a tail-recursive form is important and useful for
 functional programming in general, dealing with laziness requires a little
 more care, and often non-tail-recursive versions are preferrable. flatten
 is an example of this, the first version is better in many ways. While I
 don't believe it happens in this case, oftentimes naively writing code
 tail-recursively in Haskell will actually -make- it overflow the stack.
 Another (actual) benefit of the first version of flatten is that it will
 work on infinite lists. http://www.haskell.org/hawiki/StackOverflow gives a
 simple example and some explanation.

That page was migrated here:
http://www.haskell.org/haskellwiki/Stack_overflow

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


[Haskell-cafe] Chessboard-building in Haskell

2007-08-18 Thread Andrew Wagner
I've started a blog series on writing a chess engine in Haskell. I
just posted the second blog entry today:
http://sequence.complete.org/node/361

I suspect there's more work to be done on that function, though. It
seems like there should be a nice way to remove that flip in apply.
Any thoughts?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Old editions of The Monad.Reader lost

2007-08-18 Thread Henk-Jan van Tuyl


L.S.,

Now that all hawiki pages have been removed, we have lost some valuable  
information. For example The Monad.Reader; on  
http://www.haskell.org/haskellwiki/The_Monad.Reader it says:
  Older editions can be found on the old Haskell wiki – they haven't been  
included here for licensing reasons.
The page it links to, a hawiki page, has dissappeared. I propose to bring  
at least the The Monad.Reader pages back. Backups of these pages can be  
found at the Wayback Machine, but there is no guarantee that will always  
be there.


--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


Re: [Haskell-cafe] Chessboard-building in Haskell

2007-08-18 Thread Twan van Laarhoven

Andrew Wagner wrote:

I've started a blog series on writing a chess engine in Haskell. I
just posted the second blog entry today:
http://sequence.complete.org/node/361

I suspect there's more work to be done on that function, though. It
seems like there should be a nice way to remove that flip in apply.
Any thoughts?


The trick is that you should always prefer zipWith over zip if you have 
the chanse, tuples make life harder.


Let's use some equational reasoning:

   foldl apply emptyGameState (zip funcs fields)
 =   {- fill in 'apply' -}
   foldl (flip (ap fst snd)) emptyGS (zip funcs fields)
 =   {- write it as a lambda function to make it clearer -}
   foldl (\y (f,x) - f x y) emptyGS (zip funcs fields)
 =   {- split fold into a fold and a map -}
   foldl (\y fx - fx y) emptyGS $ map (\(f,x) - f x)
  $ (zip funcs fields)
 =   {- map . zip -- zipWith -}
   foldl (\y fx - fx y) emptyGS $ zipWith (\f x - f x) funcs fields
 =   {- use prelude functions -}
   foldl (flip ($)) emptyGS $ zipWith ($) funcs fields
 ~=  {- now, do you really want a foldl or will foldr do? -}
   foldr ($) emptyGS $ zipWith ($) funcs fields


You can now also write the function in pointfree style:

 loadFEN = foldr ($) emptyGameState
 . zipWith ($) funcs
 . words
where funcs = [parseBoard, parseCastleStatus]

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


[Haskell-cafe] How do I simulate dependent types using phantom types?

2007-08-18 Thread DavidA
Hi,

I am trying to implement quadratic fields Q(sqrt d). These are numbers of the 
form a + b sqrt d, where a and b are rationals, and d is an integer.

In an earlier attempt, I tried
data QF = QF Integer Rational Rational
(see http://www.polyomino.f2s.com/david/haskell/hs/QuadraticField.hs.txt)
The problem with this approach is that it's not really type-safe:
I can attempt to add a + b sqrt 2 to c + d sqrt 3, whereas this should be a 
type error because 2 /= 3.

So I thought I'd have a go at doing it with phantom types. In effect I'd be 
using phantom types to simulate dependent types. Here's the code:

{-# OPTIONS_GHC -fglasgow-exts #-}

import Data.Ratio

class IntegerType a where
value :: Integer

data Two
instance IntegerType Two where value = 2

data Three
instance IntegerType Three where value = 3

data QF d = QF Rational Rational deriving (Eq)

instance IntegerType d = Show (QF d) where
show (QF a b) = show a ++  +  ++ show b ++  sqrt  ++ show value

instance IntegerType d = Num (QF d) where
QF a b + QF a' b' = QF (a+a') (b+b')
negate (QF a b) = QF (-a) (-b)
QF a b * QF c d = QF (a*c + b*d*value) (a*d + b*c)
fromInteger n = QF (fromInteger n) 0

The problem is, this doesn't work. GHC complains:
The class method `value'
mentions none of the type variables of the class IntegerType a
When checking the class method: value :: Integer
In the class declaration for `IntegerType'

Is what I'm trying to do reasonable? If no, what should I be doing instead? If 
yes, why doesn't GHC like it?

Thanks, David

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


Re: [Haskell-cafe] How do I simulate dependent types using phantom types?

2007-08-18 Thread Lennart Augustsson
Use
  value :: a - Integer


On 8/18/07, DavidA [EMAIL PROTECTED] wrote:

 Hi,

 I am trying to implement quadratic fields Q(sqrt d). These are numbers of
 the
 form a + b sqrt d, where a and b are rationals, and d is an integer.

 In an earlier attempt, I tried
 data QF = QF Integer Rational Rational
 (see http://www.polyomino.f2s.com/david/haskell/hs/QuadraticField.hs.txt)
 The problem with this approach is that it's not really type-safe:
 I can attempt to add a + b sqrt 2 to c + d sqrt 3, whereas this should be
 a
 type error because 2 /= 3.

 So I thought I'd have a go at doing it with phantom types. In effect I'd
 be
 using phantom types to simulate dependent types. Here's the code:

 {-# OPTIONS_GHC -fglasgow-exts #-}

 import Data.Ratio

 class IntegerType a where
 value :: Integer

 data Two
 instance IntegerType Two where value = 2

 data Three
 instance IntegerType Three where value = 3

 data QF d = QF Rational Rational deriving (Eq)

 instance IntegerType d = Show (QF d) where
 show (QF a b) = show a ++  +  ++ show b ++  sqrt  ++ show value

 instance IntegerType d = Num (QF d) where
 QF a b + QF a' b' = QF (a+a') (b+b')
 negate (QF a b) = QF (-a) (-b)
 QF a b * QF c d = QF (a*c + b*d*value) (a*d + b*c)
 fromInteger n = QF (fromInteger n) 0

 The problem is, this doesn't work. GHC complains:
 The class method `value'
 mentions none of the type variables of the class IntegerType a
 When checking the class method: value :: Integer
 In the class declaration for `IntegerType'

 Is what I'm trying to do reasonable? If no, what should I be doing
 instead? If
 yes, why doesn't GHC like it?

 Thanks, David

 ___
 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


Re: [Haskell-cafe] How do I simulate dependent types using phantom types?

2007-08-18 Thread Twan van Laarhoven

DavidA wrote:


Hi,

I am trying to implement quadratic fields Q(sqrt d). These are numbers of the 
form a + b sqrt d, where a and b are rationals, and d is an integer.


...

class IntegerType a where
value :: Integer

The problem is, this doesn't work. GHC complains:
The class method `value'
mentions none of the type variables of the class IntegerType a
When checking the class method: value :: Integer
In the class declaration for `IntegerType'

Is what I'm trying to do reasonable? If no, what should I be doing instead? If 
yes, why doesn't GHC like it?


You are on the right track. The problem with the class method is that it 
doesn't use type 'a' anywhere, consider

 f :: Integer
 f = value
What class instance should be used here?

The solution is to use a dummy parameter:
 class IntegerType a where
 value :: a - Integer
And call it like:
 f = value (undefined :: Two)

So for instance:
 instance IntegerType d = Show (QF d) where
 show (QF a b) = show a ++  +  ++ show b ++  sqrt 
   ++ show (value (undefined::d))

The problem is that this doesn't work, because d is not in scope, you 
need the scoped type variables extension:


 valueOfQF :: forall a. IntegerType a = QF a - Integer
 valueOfQF qf = value (undefined :: a)

or maybe better, change the class:

 class IntegerType a where
 value :: QF a - Integer

Now you can simply use

 instance IntegerType d = Show (QF d) where
 show qf@(QF a b) = show a ++  +  ++ show b ++  sqrt 
 ++ show (value qf)

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-18 Thread Chaddaï Fouché
 foo n = if n0 then [] else n : foo (n-1)

 bar n = aux 0 [] where
   aux i xs = if in then xs else aux (i+1) (i:xs)

 that foo is more efficient than bar because lazy evaluation of foo just puts
 the delayed computation in the cdr of the list, while lazy evaluation of
 bar has to keep track of all aux calls (the closures) which gives much
 more overhead, maybe even stack overflow? Something like that?

There is absolutely no problem with bar, it will not stack overflow
since it _is_ tail-recursive _and_ the comparison i  n force the
evaluation of i avoiding the risk of constructing a too big thunk for
the first parameter of aux which could bring a stack overflow like in
this example :
nonStrictLength n [] = n
nonStrictLength n (_:xs) = nonStrictLength (n+1) xs

(try nonStrictLength 0 [1..1000] in GHCi to see the stack
overflow, GHC strictness analysis would avoid the problem with -O)

Though foo is still more interesting than bar since it will work on
infinite list, bar is too strict.

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


[Haskell-cafe] Re: How do I simulate dependent types using phantom types?

2007-08-18 Thread DavidA
Twan van Laarhoven twanvl at gmail.com writes:

 The solution is to use a dummy parameter:
   class IntegerType a where
   value :: a - Integer
 And call it like:
   f = value (undefined :: Two)
 
 So for instance:
   instance IntegerType d = Show (QF d) where
   show (QF a b) = show a ++  +  ++ show b ++  sqrt 
 ++ show (value (undefined::d))

Thanks to all respondents for this suggestion. That works great.

 
 The problem is that this doesn't work, because d is not in scope, you 
 need the scoped type variables extension:
 
   valueOfQF :: forall a. IntegerType a = QF a - Integer
   valueOfQF qf = value (undefined :: a)

Well actually, your first attempt *did* work for me (using GHC 6.6.1). Is this 
not behaviour that I can rely on?

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


Re: [Haskell-cafe] Sudoku Solver

2007-08-18 Thread Jon Harrop
On Saturday 18 August 2007 19:05:04 Wouter Swierstra wrote:
 I hacked up a parallel version of Richard Bird's function pearl solver:

 http://www.haskell.org/sitewiki/images/1/12/SudokuWss.hs

 It not really optimized, but there are a few neat tricks there.
 Rather than prune the search space by rows, boxes, and columns
 sequentially, it represents the sudoku grid by a [[TVar [Int]]],
 where every cell has a TVar [Int] corresponding to the list of
 possible integers that would 'fit' in that cell. When the search
 space is pruned, we can fork off separate threads to prune by
 columns, rows, and boxes -- the joy of STM!

Is it possible to write a shorter Haskell version, perhaps along the lines of 
this OCaml:

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

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

let cmp (_, a) (_, b) = compare (length a) (length b)

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

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


[Haskell-cafe] Using Apple Spotlight to search for .hs and .lhs files

2007-08-18 Thread Dan Piponi
This isn't really a Haskell question but I'm guessing some Haskell
hackers have a solution. MacOS X's Spotlight doesn't seem to be able
to search for text in .lhs and .hs files. But it can find text in .txt
files. Is there a way of getting Spotlight to treat .lhs and .hs files
like .txt files so I can instantly search all of my Haskell source?
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe