Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread Michael T. Richter
On Fri, 2007-23-02 at 02:24 -0500, Albert Y. C. Lai wrote:

 Call me a technophile, but it saddens me that ASCII has already held us 
 back for too many decades, and looks like it will still hold us back for 
 another.


OK.  You're a technophile.  But I agree with you.  ASCII needs to die a
slow, brutal death.  Quickly.  (And yes, I'm aware of the
contradiction. ;))

-- 
Michael T. Richter [EMAIL PROTECTED]
Disclaimer: Any people who think that opinions expressed from my private
email account in any way, shape or form are those of my employer have
more lawyers at their beck and call than they do brain cells.


smiley-4.png
Description: PNG image


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prime finding

2007-02-23 Thread Ruben Zilibowitz
I ran a few of the tests myself on my Mac Mini G4 with 512 Mb ram. I  
compiled the programs with ghc 6.6. I got different results however.


10^310^410^5
Reinke  0.7251  1.751   1m0.310s
Runciman0.126   1.097   5m19.569s
Zilibowitz  0.074.668   11m45.877s
NaiveSeive  0.369   47.795  -

The NaiveSeive program ran somewhat slower on my machine than it  
seemed to on yours. Also the Reinke program seemed to be faster than  
Runciman on my machine. It may be to do with not having enough ram.  
But I'm not too sure. Can you suggest any explanation for the  
different results?


Ruben

On 23/02/2007, at 4:46 PM, Melissa O'Neill wrote:


Ruben Zilibowitz wrote:
I see that there has been some discussion on the list about prime  
finding algorithms recently. I just wanted to contribute my own  
humble algorithm:


Thanks!


Comparing it to some of the algorithms in:
http://www.haskell.org/pipermail/haskell-cafe/2007-February/ 
022765.html


It seems to perform reasonably well. It also has the advantage of  
being quite short.


I've added it to my table.  It's fun to find new ways to figure out  
primes, but I think the shortness advantage goes to the naive  
primes algorithm, which is faster and shorter.


Melissa.

   --
 Time (in seconds) for Number of Primes
 
   Algorithm 10^310^4 10^5 10^6 10^7 10^8
   --
   C-Sieve   0.00  0.00 0.01 0.29  5.1288.24
   O'Neill (#2)  0.01  0.09 1.4522.41393.28 -
   O'Neill (#1)  0.01  0.14 2.9347.08 - -
   Bromage   0.02  0.39 6.50   142.85 - -
   sieve (#3)  0.01  0.25 7.28   213.19 - -
   Naive 0.32  0.6616.04   419.22 - -
   Runciman  0.02  0.7429.25- - -
   Reinke0.04  1.2141.00- - -
   Zilibowitz0.02  2.50   368.33- - -
   Gale (#1) 0.12 17.99-- - -
   sieve (#1)  0.16 32.59-- - -
   sieve (#2)  0.01 32.76-- - -
   Gale (#2) 1.36268.65-- - -
   --

___
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] Prime finding

2007-02-23 Thread Melissa O'Neill

*sigh* don't click send at 2:30am...

I wrote:
The algorithm named Naive in my table is called SimplePrimes in  
the zip file, and the example named sieve in my table is called  
NaivePrimes in the zip file.


The algorithm named Naive in my table is called SimplePrimes in the  
zip file, and the example named sieve in my table is called  
NaiveSieve in the zip file.


   Melissa.



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


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

2007-02-23 Thread ajb
G'day all.

Quoting Melissa O'Neill [EMAIL PROTECTED]:

 Cool, thanks.  When I ran your code trying to find the 10,000th
 prime, I got
AtkinSieveTest: Ix{Integer}.index: Index (36213) out of range
 ((0,36212))
 but that went away when I made your array one bigger.

Fixed, thanks.

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


[Haskell-cafe] Re: process

2007-02-23 Thread h .
I have in mind something as connections via pipes to the chils's stdin, stdout 
and stderr, but the stream library just supports internal pipes, and posix 
require Unix. By this means it's not possible to request, receive and than 
respond,... with the process. Does there exist an alternative way?

___
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 Donald Bruce Stewart
h._h._h._:
 I have in mind something as connections via pipes to the chils's stdin, 
 stdout 
 and stderr, but the stream library just supports internal pipes, and posix 
 require Unix. By this means it's not possible to request, receive and than 
 respond,... with the process. Does there exist an alternative way?
 

I usually use System.Process for this kind of thing.

http://haskell.org/ghc/docs/latest/html/libraries/base/System-Process.html

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


Re: [Haskell-cafe] TFP 2007: Registration and Program

2007-02-23 Thread TFP 2007
 
 Dear Colleagues,
 
 You may now resgister for TFP 2007! TFP 2007 will be held April 2-4,
 2007 in New York City, USA.


 April 2 is the first night of Passover.  This is not one of those

Your point is well taken. It is very unfortunate that the overlap you have 
pointed out exists. The organizing committee had to consider _many_ 
variables including, among others, the availability of a venue and of 
hotels for participants in NYC. Sometimes the logistics of a situation 
force your hand.




Dr. Marco T. Morazan
TFP 2007
Program Committee Chair
http://cs.shu.edu/tfp2007/___
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 Thomas Hartman

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.

Can anyone see what I'm doing wrong?

In case it matters, I'm on a virtualized user-mode-linux shell.

**
[EMAIL PROTECTED]:~/learning/haskell/inter-process-communication$
cat /proc/version
Linux version 2.4.29-linode39-1um ([EMAIL PROTECTED]) (gcc
version 3.3.3 20040412 (Red Hat Linux 3.3.3-7)) #1 Wed Jan 19 12:22:14
EST 2005

[EMAIL PROTECTED]:~/learning/haskell/inter-process-communication$
ghc -v 21 | head -n1
Glasgow Haskell Compiler, Version 6.6, for Haskell 98, compiled by GHC
version 6.6
[EMAIL PROTECTED]:~/learning/haskell/inter-process-communication$
cat inter-process-communication.hs
module Main where
import System.Process
import System.IO

main :: IO ()
main = do
   putStrLn Running BC
   (inp,out,err,pid) - runInteractiveProcess bc [] Nothing Nothing
   hSetBuffering inp LineBuffering
   hSetBuffering out LineBuffering
   hSetBuffering err LineBuffering
   hPutStrLn inp 1+3
   a - hGetLine out
   hPutStrLn inp a
   a - hGetLine out
   hPutStrLn inp quit
   waitForProcess pid
   putStrLn a
[EMAIL PROTECTED]:~/learning/haskell/inter-process-communication$
runghc inter-process-communication.hs
Running BC
*** Exception: waitForProcess: does not exist (No child processes)
[EMAIL PROTECTED]:~/learning/haskell/inter-process-communication$


2007/2/23, Jules Bean [EMAIL PROTECTED]:

h. wrote:


 If it basically works, what goes wrong in my programm?



Well that depends entirely what your program is supposed to do.

Your email doesn't tell us (a) what your program was supposed to do or
(b) what goes wrong. Therefore we are forced to guess!

The following slight variation of your program works fine for me. I
don't have anything called 'prog1' on my system, so I used 'bc' which is
a calculator program standard on unixes, which works by line-by-line
interaction. I varied your program just a tiny bit to get some
interesting output:

module Main where
import System.Process
import System.IO

main :: IO ()
main = do
putStrLn Running BC
(inp,out,err,pid) - runInteractiveProcess bc [] Nothing Nothing
hSetBuffering inp LineBuffering
hSetBuffering out LineBuffering
hSetBuffering err LineBuffering
hPutStrLn inp 1+3
a - hGetLine out
hPutStrLn inp a
a - hGetLine out
hPutStrLn inp quit
waitForProcess pid
putStrLn a



This program asks 'bc' to calculate 1+3.  The reply is stored in 'a'.
Then the program sends 'a' back to bc, effectively asking bc to
calculate 4. Since the 4 evaluates just to 4, 'a' gets the value
4 once more.

Then I have to send quit to bc. That is the command that bc
interprets as an instruction to quit; without that command,
'waitForProcess pid' will wait forever (it's waiting for bc to quit).

Finally my program outputs 4 the result of the last calculation.

Is this close to what you're trying to do?

Jules
___
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] 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


[Haskell-cafe] Re: process

2007-02-23 Thread h .
Jules Bean jules at jellybean.co.uk writes:
 Well that depends entirely what your program is supposed to do.
 
 Your email doesn't tell us (a) what your program was supposed to do or 
 (b) what goes wrong. Therefore we are forced to guess!
 
 The following slight variation of your program works fine for me. I 
 don't have anything called 'prog1' on my system, so I used 'bc' which is 
 a calculator program standard on unixes, which works by line-by-line 
 interaction. I varied your program just a tiny bit to get some 
 interesting output:
 
 module Main where
 import System.Process
 import System.IO
 
 main :: IO ()
 main = do
 putStrLn Running BC
 (inp,out,err,pid) - runInteractiveProcess bc [] Nothing Nothing
 hSetBuffering inp LineBuffering
 hSetBuffering out LineBuffering
 hSetBuffering err LineBuffering
 hPutStrLn inp 1+3
 a - hGetLine out
 hPutStrLn inp a
 a - hGetLine out
 hPutStrLn inp quit
 waitForProcess pid
 putStrLn a
 
 This program asks 'bc' to calculate 1+3.  The reply is stored in 'a'. 
 Then the program sends 'a' back to bc, effectively asking bc to 
 calculate 4. Since the 4 evaluates just to 4, 'a' gets the value 
 4 once more.
 
 Then I have to send quit to bc. That is the command that bc 
 interprets as an instruction to quit; without that command, 
 'waitForProcess pid' will wait forever (it's waiting for bc to quit).
 
 Finally my program outputs 4 the result of the last calculation.
 
 Is this close to what you're trying to do?
 
 Jules
 

Thanks, but I still puzzle over the same problem.
I wrote the following lines to test exactely your code:

module Main where
main :: IO ()
main = f
  where
  f = do
a - getLine
if a == quit then return () else putStrLn a  f

running the program in the console works without any problems (1+3 is the 
result :) ), but with runInteractiveProcess I do not get any output 
except Running BC, and every IO action after the first hPutStrLn inp 1+3 is 
never reached (the program hang-up there - no error is thrown) - thats my 
problem...

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


[Haskell-cafe] Illegal polymorphic or qualified type: forall l.

2007-02-23 Thread Marc Weber
how can i fix this?
Mmmh I really need some haskell type class traingings ;)

= test file ==
module Main where
import HList
import HOccurs
import Control.Monad.Reader

class Get a b where
  get :: a - b

data D1 = D1 Int -- dummy type

type ActionMonad a l = forall l. (HOccurs D1 l)
   = ( ReaderT l IO a )

data CR = CR (ActionMonad Bool ()) 

instance Get CR (ActionMonad Bool ()) where
  get (CR a) = a

main = do
  print test

= error ==
|| [1 of 1] Compiling Main ( uqt.hs, uqt.o )
|| 
uqt.hs|16| 0:
|| Illegal polymorphic or qualified type: forall l.
|| (HOccurs D1 l) =
|| ReaderT l IO Bool
|| In the instance declaration for `Get CR (ActionMonad Bool ())'

==

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


Re: [Haskell-cafe] Re: Map list of functions over a single argument

2007-02-23 Thread Martin DeMello

On 2/22/07, Gene A [EMAIL PROTECTED] wrote:

 The functions as I originally defined them are probably
easier for someone new to Haskell to understand what was going on than the
rather stark ($ a) in the final factoring of the function... Though the
final resulting function is far the cleaner for that notation!


This is what I came up with when I was experimenting:

map (\f - f $ a) fs

which then helped me to see it could be rewritten as just map ($ a) fs

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


[Haskell-cafe] EnumSet and EnumMap

2007-02-23 Thread Chris Kuklewicz
I could not quickly find anyone else writing this boiler plate, so I have posted
 this useful wrapper on the Haskell wiki at
http://haskell.org/haskellwiki/EnumSet_EnumMap

This uses a cheap newtype to wrap IntSet and IntMap so that you can store any
Enum in them.  It saves either writing many toEnum/fromEnum functions or using
the slower and more generic Data.Set and Data.Map.

The original motivation was to go from Map Char to IntMap.

And as a bonus, the type signature of the newtype is the same kind as Data.Set
and Data.Map (which matters when declaring instances...)

 newtype EnumSet e = EnumSet {unEnumSet :: S.IntSet}
   deriving (Monoid,Eq,Read,Show,Ord)

 newtype EnumMap k a = EnumMap {unEnumMap :: M.IntMap a}
   deriving (Eq,Read,Show,Ord,Monoid,Foldable,Functor)

This has been quickly tested with GHC 6.6 and may contain typographical errors I
have not caught yet.

-- 
Chris

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


Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-23 Thread Neil Mitchell

Hi Nick


That sounds like a great option. Candidate numero uno as of now. What
I have in mind right now should be pretty light weight, but it will
mostly be a regurgitation of code I've seen floating around. Some of
the code from the previous wiki link, type-level decimal numbers I saw
in an Oleg paper (I think), etc.


I am happy to accept a Safe list implementation much the same way as
Oleg's implementation. The Safe library is a place to put code which
allows the user to write code which ensures their are no pattern match
errors, or to give better error messages when there are pattern match
errors.

Something like a type level implementation of decimals, if not
directly concerned with this, might be better in a separate library
for type level computation. Something like
http://www.eecs.tufts.edu/~rdocki01/typenats.html



Would you be open to such code in your library? Anyone have a better
place for it?


Yep, just send in a patch :)

Thanks

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


Re: [Haskell-cafe] exists . a psuedo-standard non-empty list module

2007-02-23 Thread Neil Mitchell

Hi


Incidentally, inserting NList into the existing Safe.List does not
seem like a good match as NList critically relies on being in a
separate module with a limited export.


As mentioned before, Safe.List would be an entirely separate module in
my package, so can export/not export whatever it chooses.


 * Catch: http://www-users.cs.york.ac.uk/~ndm/projects/catch.php
 * ESC-Haskell: http://www.cl.cam.ac.uk/~nx200/research/escH-hw.ps

I would submit the approach of the lightweight static capabilities (cf
above Wiki link) to be counted as the third project in that area. The
latter has an advantage that it is available in Haskell right now and
requires no extra tools.


I've added a link to my web page, which is where I also paste from
where someone asks this question :)

Thanks

Neil
___
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 Bryan O'Sullivan

Dougal Stanton wrote:


If it basically works, what goes wrong in my programm?


Maybe something to do with compiler flags?


No.  This isn't even a Haskell-related problem, in all likelihood.

Bidirectional interaction with another process over a pipe, particularly 
when the other process is using stdio or an equivalent (i.e. most 
programs), is a classic and fruitful source of deadlocks.


Just because *your* end of each pipe is a line-buffered file handle has 
no bearing on the *other* process's management of its pair of endpoints. 
 For example, on a Unix-like system, the other process's stdio will 
block-buffer stdin and stdout by default if it finds that they're not 
attached to tty-like file descriptors.


There are really only two ways to deal with this.  The first is to read 
from the subprocess in a separate thread, but this only works 
effectively if what you're sending to the other process doesn't depend 
on what you read back from it (because there's no way of forcing it to 
send you anything).


The second is Unix-specific, and involves talking to the other process 
via a pseudotty instead of a pair of pipes.  This convinces the other 
process's stdio that you're a terminal, and you get the line-buffering 
you desire.  It's *still* highly deadlock-prone, and not something to do 
casually.


So what you're trying to do looks easy if you've never tried it, but 
it's actually very fiddly in all but the most trivial of circumstances.


The third, and best, way to deal with this problem is to completely 
avoid it unless you want to spend several hours or days scratching your 
head.


b
___
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 Bryan O'Sullivan

Bryan O'Sullivan wrote:

Just because *your* end of each pipe is a line-buffered file handle has 
no bearing on the *other* process's management of its pair of endpoints. 
 For example, on a Unix-like system, the other process's stdio will 
block-buffer stdin and stdout by default if it finds that they're not 
attached to tty-like file descriptors.


In case the implications of this aren't clear, let me expand a little.

You've got a line-buffered stdout.  You write 1+1\n, which sends 4 
bytes to the other process.


It's got a block-buffered stdin, so it's going to sit in its first read 
until it receives 512 bytes (or whatever the buffer size is) from you. 
And an oversized violin, you have a deadlock!


The converse bites you, too.  You want to read a line from the other 
process.  It writes 1+1\n to you, but its stdio buffers up the 4 bytes 
because it hasn't reached the 512-byte watermark.  It then tries to read 
from you, but you're still blocked trying to read the first line (that 
it hasn't actually sent) from it.  Deadlock.


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


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread Steve Schafer
On Fri, 23 Feb 2007 18:09:15 +, you wrote:

Well, actually, I never cited the non-breaking space character as a 
problem.

Well, actually, you did:

Symbols such as the 160 used liberally in the Haskell wikibook are
totally invisible to screen readers.

 #160; = NO BREAK SPACE

Which is why I asked specifically about that.

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] Re: process

2007-02-23 Thread h .
Albert Y. C. Lai trebla at vex.net writes:

 
 h. wrote:
  module Main where
  main :: IO ()
  main = f
where
f = do
  a - getLine
  if a == quit then return () else putStrLn a  f
 
 This one also needs to switch to line buffering. Add/Change:
 
 import System.IO(stdout, hSetBuffering, BufferMode(LineBuffering))
 main = hSetBuffering stdout LineBuffering  f
 


Thanks a lot, now it does work!
This means just the proc1 program has to be changed and everything will work 
properly (hopefully - at least the haskell part works :) ).


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


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread P. R. Stanley
So that's what it is! I wondered why alt-num-0160 only produced a 
space character. Still, as I said originally, it is totally invisible 
in the browse buffer.
Anyway, are you one of the authors of the wikibook Or, are you just 
offering your assistance?


All the best
Paul
At 19:03 23/02/2007, you wrote:

On Fri, 23 Feb 2007 18:09:15 +, you wrote:

Well, actually, I never cited the non-breaking space character as a
problem.

Well, actually, you did:

Symbols such as the 160 used liberally in the Haskell wikibook are
totally invisible to screen readers.

 #160; = NO BREAK SPACE

Which is why I asked specifically about that.

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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread Seth Gordon
P. R. Stanley wrote:
 I'm referring to math symbols which do not get successfully
 translated into an intelligible symbol in the screen reader browse buffer.

Is there a way to make the symbols both look right on a screen and sound
right from a screen reader?  E.g.,

span title=big sigmaΣ/span  !-- there's a U+03A3 in there --
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread David House

On 23/02/07, P. R. Stanley [EMAIL PROTECTED] wrote:

As a tip for anyone involved in writing and publishing scientific
materials on the web, unless the maths is either written without any
funny symbols or, better still, typeset in latex, it is not
accessible to a screen-reader.


I was under the impression that modern screen readers could pronounce
Unicode characters by looking up their name. I.e., your #160; would
get read as 'Non-breaking space' (perhaps a bad example, this one
wouldn't want to be read out due to its abuse as a layout tool, which
would make reading old pages very awkward).

I don't see how images are going to be much better? I suppose math
images do, on MediaWiki, have an alt text which is their LaTeX, but
I'd hate to have to have that read to me.

If you're interested in talking to the authors of the wikibook,
subscribe to the wikibook@haskell.org mailing list.

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


[Haskell-cafe] How to build a generic spreadsheet?

2007-02-23 Thread Greg Fitzgerald

I want to write a program where a user would update a bunch of variables,
and everything that depends on those variables (and nothing else) are
recalculated.  Basically, a spreadsheet, but generalized for any
computation.  Could someone recommend an elegant way to do it or some good
reading material?

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


Re: [Haskell-cafe] How to build a generic spreadsheet?

2007-02-23 Thread the Edward Blevins
On Fri, Feb 23, 2007 at 02:33:00PM -0800, Greg Fitzgerald wrote:
 I want to write a program where a user would update a bunch of variables,
 and everything that depends on those variables (and nothing else) are
 recalculated.  Basically, a spreadsheet, but generalized for any
 computation.  Could someone recommend an elegant way to do it or some good
 reading material?

http://www.cse.ogi.edu/~magnus/Adaptive/

That might be a good place to start.

-- 
the Edward Blevins   [EMAIL PROTECTED](512) 796-6661
Today is Prickle-Prickle, the 54th day of Chaos in the YOLD 3173
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to build a generic spreadsheet?

2007-02-23 Thread Sebastian Sylvan

On 2/23/07, Sebastian Sylvan [EMAIL PROTECTED] wrote:

On 2/23/07, Greg Fitzgerald [EMAIL PROTECTED] wrote:
 I want to write a program where a user would update a bunch of variables,
 and everything that depends on those variables (and nothing else) are
 recalculated.  Basically, a spreadsheet, but generalized for any
 computation.  Could someone recommend an elegant way to do it or some good
 reading material?

Off the top of my head, one cool way of doing it would be to have each
variable be a separate thread (they're lightweight, so it's okay!
:-)), and you would have a list of input connections and output
connections, in the form of TVars.

In its resting state you would have a transaction which simply reads
all of the input variables, and returns the new list of inputs if and
only if either of them are changed, something like:

-- not compiled, consider it pseudocode :-)
getInputs :: (Eq a ) = [( a, TVar a)] - STM [a]
getInputs inp = do
  let (vals, vars) = unzip inp
  newVals - mapM readTVar vars
  when ( newVals /= vals ) retry -- at least one input must've been changed


Bah, this should be:

when ( newVals == vals ) retry

Of course...

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to build a generic spreadsheet?

2007-02-23 Thread Bryan O'Sullivan

Greg Fitzgerald wrote:
I want to write a program where a user would update a bunch of 
variables, and everything that depends on those variables (and nothing 
else) are recalculated.


http://sigfpe.blogspot.com/2006/11/from-l-theorem-to-spreadsheet.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread P. R. Stanley



As a tip for anyone involved in writing and publishing scientific
materials on the web, unless the maths is either written without any
funny symbols or, better still, typeset in latex, it is not
accessible to a screen-reader.


I was under the impression that modern screen readers could pronounce
Unicode characters by looking up their name. I.e., your #160; would
get read as 'Non-breaking space' (perhaps a bad example, this one
wouldn't want to be read out due to its abuse as a layout tool, which
would make reading old pages very awkward).

I don't see how images are going to be much better? I suppose math
images do, on MediaWiki, have an alt text which is their LaTeX, but
I'd hate to have to have that read to me.





I think latex is the perfect solution to the problem. It is 
perhaps the only 100 percent accessible medium available right now. 
It doesn't require any special software to read. All it needs is a 
simple text editor.



Latex is a well-established tool/medium in the world-wide scientific 
community and therefore its inclusion in the Haskell wikibook or any 
other scientific document along with the unicode characters and 
image files would be potentially beneficial to everyone.

Paul




If you're interested in talking to the authors of the wikibook,
subscribe to the wikibook@haskell.org mailing list.

--
-David House, [EMAIL PROTECTED]


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


Re: [Haskell-cafe] How to build a generic spreadsheet?

2007-02-23 Thread Neil Mitchell

Hi


I want to write a program where a user would update a bunch of variables,
and everything that depends on those variables (and nothing else) are
recalculated.  Basically, a spreadsheet, but generalized for any
computation.  Could someone recommend an elegant way to do it or some good
reading material?


PropLang already has the framework to do this:

http://www.cs.york.ac.uk/fp/darcs/proplang/

Take a look at the samples, you can say something like:

sb!text = (\x - Word count:  ++ show (length $ words x)) =$$= txt!text

The status bar's text is the word count, and its automatically updated
if the user types.

PropLang mainly operates with Gtk, but the framework is more general.

What it does lack is much documentation :)

Thanks

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


Re: [Haskell-cafe] A real Haskell Cookbook

2007-02-23 Thread P. R. Stanley



Is there a way to make the symbols both look right on a screen and sound
right from a screen reader?  E.g.,

span title=big sigmaΣ/span  !-- there's a U+03A3 in there --
In theory the title attribute should be the 
adequate yet simple solution we're after. Sadly, 
in reality this 'aint the case. The title 
attribute works beautifully in list and table elements.


Having read some of the posts I've come to the 
conclusion that the addition of Latex source 
code along with the unicode stuff may be the best way forward.
I am, however, still open to new ideas. So 
please don't hesitate to keep them coming.
By the way guys, if we're straying off-topic 
here please feel free to drop me a line privately.

Best wishes
Paul


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


[Haskell-cafe] beginner question re example in Hutton's Programming in Haskell

2007-02-23 Thread David Cabana
I have been trying to work through Graham Hutton's Programming in  
Haskell, but have hit something of a snag in chapter 8.4. Hutton  
presents some sample code which I am trying to run, with no luck so  
far. Here is the code as I constructed it by gathering snippets  
presented across three pages.

code
module Main where

-- as per Hutton page 75
type Parser a = String - [(a, String)]

-- page 75
return :: a - Parser a
return v = \inp - [(v,inp)]

-- page 76
failure :: Parser a
failure = \inp - [ ]

item :: Parser Char
item = \inp - case inp of
[ ] - [ ]
(x:xs)- [(x,xs)]

parse :: Parser a - String - [(a,String)]
parse p inp = p inp

-- page 77
p :: Parser (Char, Char)
p = do x - item
item
y - item
return (x,y)
/code

When I tried to load this code, I got this error message:

Ambiguous occurrence `return'
It could refer to either `return', defined at /Users/joe/haskell/ 
parse2.hs:8:0

  or `return', imported from Prelude

OK. My reasoning was that Hutton took the trouble to define return,  
so I decided to use the local definition instead of the one in the  
Prelude. I changed the last line from return (x,y) to Main.return  
(x,y). The new error message is worse:


Couldn't match expected type `Char'
   against inferred type `[(Char, String)]'
In the expression: x
In the first argument of `return', namely `(x, y)'
In the expression: return (x, y)/blockquote

Hutton provided explicit type signatures, so I did not expect type  
issues.


I decided to take another approach. The book has a website that lists  
errata and provides code listings. The code for chapter eight is at  
http://www.cs.nott.ac.uk/~gmh/Parsing.lhs


When I read Hutton's code, I noticed that he begins by importing  
Monad. The code I list above is from chapter 8, pages 75-77 of the  
book. Monads have not yet been mentioned. The book's index shows that  
monads aren't mentioned till page 113, in chapter 10. I also notice  
that in his code, Hutton makes repeated use of a symbol P whose  
meaning I do not know.


What do I have to do to make this code work?

I know I can use Hutton's code from the website, but I expected the  
code presented in the book to work, or the code on the website to  
restrict itself to what has been discussed in the book. Am I missing  
something here?


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


Re: [Haskell-cafe] beginner question re example in Hutton's Programming in Haskelly

2007-02-23 Thread Stefan O'Rear
On Fri, Feb 23, 2007 at 11:18:46PM -0500, David Cabana wrote:
 I have been trying to work through Graham Hutton's Programming in  
 Haskell, but have hit something of a snag in chapter 8.4. Hutton  
 presents some sample code which I am trying to run, with no luck so  
 far. Here is the code as I constructed it by gathering snippets  
 presented across three pages.
 code
 module Main where
 
 -- as per Hutton page 75
 type Parser a = String - [(a, String)]
 
 -- page 75
 return :: a - Parser a
 return v = \inp - [(v,inp)]

This return conflicts with the one in Prelude, and (while similar) they
are not interchangable.

 -- page 76
 failure :: Parser a
 failure = \inp - [ ]

This is analogous to Prelude.fail.  Fortunately Hutton didn't call it that :)

 item :: Parser Char
 item = \inp - case inp of
 [ ] - [ ]
 (x:xs)- [(x,xs)]

Looks reasonable

 parse :: Parser a - String - [(a,String)]
 parse p inp = p inp

Same here

 -- page 77
 p :: Parser (Char, Char)
 p = do x - item
 item
 y - item
 return (x,y)
 /code

Bad!

Due to the Layout Rule that is parsed as a single long statement...
I'm quite suprised you didn't get a parse error. 

It needs to be:

p :: Parser (Char, Char)
p = do x - item
   item
   y - item
   return (x,y)

But, this still won't work.  essentially the 'do' uses Prelude.return,
Prelude.(), and Prelude.(=), which work on defined Monads; but your
parser type is not properly declared as a monad.  (and cannot be, because
it is a type synonym.)

You could define:

() :: Parser x - Parser y - Parser y
(p1  p2) l = [ (s,rs2) | (f,rs1) - p1 l , (s,rs2) - p2 rs1 ]

(=) :: Parser x - (x - Parser y) - Parser y
(p1 = fn) l = [ (s,rs2) | (f,rs1) - p1 l , (s,rs2) - fn f rs1 ]

then use those (do-notation ignores scope so it must be desugared):

p :: Parser (Char, Char)
p = item  Main.= \x -
item  Main.
item  Main.= \y -
Main.return (x,y)

This should work.  Famous last words I know :)

 When I tried to load this code, I got this error message:
 
 Ambiguous occurrence `return'
 It could refer to either `return', defined at /Users/joe/haskell/ 
 parse2.hs:8:0
 or `return', imported from Prelude
 
 OK. My reasoning was that Hutton took the trouble to define return,  
 so I decided to use the local definition instead of the one in the  
 Prelude. I changed the last line from return (x,y) to Main.return  
 (x,y). The new error message is worse:
 
 Couldn't match expected type `Char'
  against inferred type `[(Char, String)]'
 In the expression: x
 In the first argument of `return', namely `(x, y)'
 In the expression: return (x, y)/blockquote
 
 Hutton provided explicit type signatures, so I did not expect type  
 issues.
 
 I decided to take another approach. The book has a website that lists  
 errata and provides code listings. The code for chapter eight is at  
 http://www.cs.nott.ac.uk/~gmh/Parsing.lhs
 
 When I read Hutton's code, I noticed that he begins by importing  
 Monad. The code I list above is from chapter 8, pages 75-77 of the  
 book. Monads have not yet been mentioned. The book's index shows that  
 monads aren't mentioned till page 113, in chapter 10. I also notice  
 that in his code, Hutton makes repeated use of a symbol P whose  
 meaning I do not know.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders

2007-02-23 Thread oleg

Perhaps you might want include in your test the following:

  http://www.haskell.org/pipermail/haskell-cafe/2007-February/022437.html

It seems quite close to the genuine Eratosthenes sieve algorithm: it
employs the idea of marks, it can cross composite numbers off several
times, and it never tries to divide or examine prime numbers. In fact,
the algorithm doesn't even use the full division or full comparison
(let alone other arithmetic operations).

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