Re: [Haskell-cafe] Mathematica

2007-05-11 Thread Joe Thornber

On 11/05/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Hi folks.

How difficult would it be to implement Mathematica in Haskell?


The language itself; very easy I'd say.  The maths libraries ...
years.  So if you just want something to play with I'm sure you could
get something working quickly.  I'd be interested in helping out.

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Joe Thornber

On 26/04/07, Bas van Dijk [EMAIL PROTECTED] wrote:

test = putStrLn $ toIsString $ do I
   need
   MultiLine
   String
   literals!


but it's simpler to just write something like:

test  = putStr $ unlines [I,
  need,
  multiline,
  string,
  literals]

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


Re: [Haskell-cafe] newbie question on ordering

2007-04-23 Thread Joe Thornber

On 22/04/07, Nikolay Metchev [EMAIL PROTECTED] wrote:

Hello guys,
I have decided to try and get back into Haskell recently. I have used it in
the past but have forgotten large chunks.
I am trying to express the logic of a particular card game. For this purpose
I need to be able to order cards in various orders. At first I thought that
the Ord class was my answer but I found it very verbose. Below is my best
attempt so far but I can't help but feel it too is verbose and that there
must be a better way of comparing cards in different orders.


I wrote some code for comparing poker hands that you may find useful
[1].  It gives each hand a classification, and then orders first on
the classification, and then on some secondary property of the
classification (eg, highest card in hand).

- Joe

[1] http://www.lambda-software.com/darcs/programming-challenges/2.8.2/poker.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell spacing problem.

2007-03-09 Thread Joe Thornber

On 09/03/07, Frozz [EMAIL PROTECTED] wrote:

Hi Haskell ppl,

I'm trying to solve a problem that had been bothering me for a long time. I'm
trying to create index and display the index in Hugs as well as an output text
file.


dispTable is a pure function so you'll get the same result
irrespective of what you do with the resulting string (ie. display it
in Hugs or write it to a file).  Are you _sure_ you're giving this
function the same input (eg, is there maybe some extra whitespace or
non-printable characters) ?

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


Re: [Haskell-cafe] Re: process

2007-02-23 Thread Joe Thornber

On 23/02/07, Thomas Hartman [EMAIL PROTECTED] wrote:

This seemed like a handy thing to have an example of, so I added it to
my growing repo of sample haskell programs and tried running it. But I
was unsuccessful.


Your program works for me both compiled or using runghc:

Linux lonlsd62 2.6.9-11.ELsmp #1 SMP Fri May 20 18:26:27 EDT 2005 i686
i686 i386 GNU/Linux
Glasgow Haskell Compiler, Version 6.6, for Haskell 98, compiled by GHC
version 6.6
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-02-22 Thread Joe Thornber

On 22/02/07, Melissa O'Neill [EMAIL PROTECTED] wrote:

But talk is cheap.  What about some actual numbers, and some code for
some actual implementations...?


Perhaps you could go the last 1% and upload a Primes package to
Hackage and forever save us from inferior sieves ?  (I enjoyed your
paper BTW).

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


Re: [Haskell-cafe] Newbie: generating a truth table

2007-02-21 Thread Joe Thornber

On 2/10/07, Peter Berry [EMAIL PROTECTED] wrote:
Prelude putStrLn $ concatMap (flip (++)\n) $ map show $ [(x,y,() x y)
|x - [True,False],y - [True,False]]


This can be simplified slightly to:

Prelude  putStrLn . unlines . map show $ [(x, y, x  y) | x -
[True, False], y - [True, False]]


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


Re: Stack usage with a state monad

2004-01-02 Thread Joe Thornber
On Fri, Jan 02, 2004 at 02:46:04PM +, Graham Klyne wrote:
 If your calculation really needs to update the cache state as it goes 
 along, then I agree that it needs to be run in the state monad.  But even 
 then, I'd be inclined to look for sub-calculations that can be evaluated as 
 ordinary functions.

I think I do need to update the cache state, though I do think I could
still split the function into 2 mutually recursive functions (both
returning the state monad) as you suggest, which would at least make
the code clearer.

 Anyway, I think I've probably added enough noise to this debate.  Whatever 
 approach you may use, have fun!

Thanks for your help.

- Joe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-31 Thread Joe Thornber
On Wed, Dec 31, 2003 at 11:54:27AM +, Graham Klyne wrote:
 My *intuition* here is that the problem is with countLeaves2, in that it 
 must build the computation for the given [sub]tree before it can start to 
 evaluate it.  Maybe this is why other responses talk about changing the 
 state monad?
 
 But why does this computation have be done in a state monad at 
 all?  countLeaves seems to me to be a pretty straightforward function from 
 a Tree to an Int, with no need for intervening state other than to 
 increment a counter:  as such, I'd have expected a simple recursive 
 function to serve the purpose.  (Maybe there was something in the original 
 application that was lost in the problem isolation?)

I think you might well be correct that I'm doing things the wrong way.
The original program is a chess prog. and the function in question is
the alphabeta search.  I wanted to hold the transposition table (a
cache of seen positions) among other things in the state monad.  I
thought this was the normal way to approach this, but am having doubts
now.  The recursive approach will indeed work, but I had hoped to
avoid all the code associated with threading the state by hand.

- Joe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-31 Thread Joe Thornber
On Wed, Dec 31, 2003 at 02:38:06PM +, Graham Klyne wrote:
  getOrCachePositionValue pos =
 do { mcache - gets (findPos pos) -- Query cache for position
; case mcache of
Just cached - return (cachedVal cached)  -- Return cached value
Nothing --- Not in cache:
   do { let val = calculatePosVal pos -- Calculate new value
  ; modify (addToCache pos val)   -- Cache new value
  ; return val-- Return new value
  }
}
 
 (This code of off-the-cuff, and may contain errors)
 
 My point is that the function 'calculatePosVal' used here to evaluate a 
 position not in the cache simply returns the calculated value, not a 
 monad.  This function is wrapped in high level code that queries and/or 
 updates the cache which is kept in a state monad.  Thus, the return type of 
 'getOrCachePositionValue' would be a monad of the appropriate type.

But I want calculatePosVal to use the cache too :(

- Joe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Stack usage with a state monad

2003-12-30 Thread Joe Thornber
Hi,

I was wondering if anyone could give me some help with this problem ?

I'm trying to hold some state in a StateMonad whilst I iterate over a
large tree, and finding that I'm running out of stack space very
quickly.  The simplified program below exhibits the same problem.

This is the first time I've hit space problems in Haskell, I hope
judicial use of 'seq' or '$!' would be enough to fix it, but I don't
know where to start.

Any ideas as to what I'm doing wrong would be much appreciated.

Thanks,

- Joe




module Main (main) where

-- Program to count the leaf nodes in a rose tree.  Written to try and
-- reproduce a stack space leak present in a larger program.

-- How can I use a state monad to count the leaves without eating all
-- the stack ?

import Control.Monad.State

data Tree = Tree [Tree] | Leaf

buildTree :: Int - Int - Tree
buildTree order = buildTree'
where
buildTree' 0 = Leaf
buildTree' depth = Tree $ map (buildTree') $ take order $ repeat (depth - 1)

countLeaves1 :: Tree - Int
countLeaves1 (Tree xs) = sum $ map (countLeaves1) xs
countLeaves1 (Leaf) = 1

incCount :: State Int ()
incCount = do {c - get;
   put (c + 1);
   return ();
  }

countLeaves2   :: Tree - Int
countLeaves2 t = execState (aux t) 0
where
aux :: Tree - State Int ()
aux (Tree xs) = foldr1 () $ map (aux) xs
aux (Leaf) = incCount

main :: IO ()B
main = print $ countLeaves2 $ buildTree 15 6
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Stack usage with a state monad

2003-12-30 Thread Joe Thornber
On Tue, Dec 30, 2003 at 08:28:11PM +0100, Tomasz Zielonka wrote:
 On Wed, Dec 31, 2003 at 02:54:18AM +0900, Koji Nakahara wrote:
  Hi,
  
  I think the problem is in the State Monad itself;
  State Monad is lazy to compute its state.
  
  I am not a haskell expert, and there may be better ideas.  But anyhow,
  when I use these = and  instead of = and , 
  your example runs fine.  I hope it becomes some help.
  
  m = k = State $ \s - let (a, s') = runState m s
  in  s `seq` runState (k a) s' -- force evaluation of the 
  state
  
  m  k = m = \_ - k
 
 Ahh, right. So I didn't have to use UnboxedState. StrictState would do.


Thankyou both for your help, I wouldn't have thought of changing the
State monad itself.  I guess I've got lots more to learn :)

- Joe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe