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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/ha
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/
02276
Bulat Ziganshin asked:
but how it looks compared with classic C implementation of sieve
algorithm?
It's still worse. I Googled for a "typical" implementation and added
it to the collection. The best Haskell implementation is still about
two orders of magnitude slower, but remember that t
Andrew and co,
I have a big fat apology to make. It was actually the wikipedia page
on Lambda Calculus where there are many occurrences of special symbols.
The Wikibook, as far as I've explored, is fully accessible.
Nonetheless, I'd still be more than happy to make my contributions in
any way I
On Thu, Feb 22, 2007 at 07:34:36PM -0800, Stefan O'Rear wrote:
> This really smells like a violation of the "monomorphism
> restriction"[1]. Try again with -fno-monomorphism-restriction, and if
> that fixes it, add a type signature to fix it for good.
>
> [1] http://haskell.org/onlinereport/decls
This really smells like a violation of the "monomorphism
restriction"[1]. Try again with -fno-monomorphism-restriction, and if
that fixes it, add a type signature to fix it for good.
[1] http://haskell.org/onlinereport/decls.html#sect4.5.5
Stefan
___
H
Having the module given below I can't see why using
printAndRerun l1
printAndRerun2 l2
but not
printAndRerun l1
printAndRerun l2
?
They only differ in their name.
Can you point me in the right direction?
{-# OPTI
h. wrote:
But it does not work as I expected. As long as there is no need to put some
input after having received some output it is no problem, but real interaction
seems not possible.
Right, this particular program works just for a particular interaction.
What real interaction do you have in
On Feb 22, 2007, at 14:56 , Henning Thielemann wrote:
On Wed, 21 Feb 2007 [EMAIL PROTECTED] wrote:
Albert Y. C. Lai wrote:
[EMAIL PROTECTED] wrote:
Albert Y. C. Lai wrote:
If and only if the database is a purely functional immutable data
structure, this can be done. [...]
Many interestin
G'day all.
Quoting Melissa O'Neill <[EMAIL PROTECTED]>:
> But talk is cheap. What about some actual numbers, and some code for
> some actual implementations...?
Just to fill out the implementations:
http://andrew.bromage.org/darcs/numbertheory/
Math/Prime.hs has an implementation of the
Hello Melissa,
Thursday, February 22, 2007, 9:54:38 AM, you wrote:
> - O'Neill (#1) is the algorithm of mine discussed in http://
> www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf
but how it looks compared with classic C implementation of sieve algorithm?
--
Best regards,
Bulat
On 2/22/07, Ruben Zilibowitz <[EMAIL PROTECTED]> 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:
[snip]
Comparing it to some of the algorithms in:
http://www.haskell.org/pipermail/haskell
> I assume that there is no way to change the date for *this* conference;
> it would require renegotiating agreements and rejuggling schedules with
> too many actors (hotels, restaurants, important speakers, etc.).
>
> But I would like everyone involved in planning *future* conferences to
> keep t
Murray Gross wrote:
> First, I suspect that the date is now cast in stone and cannot be
> changed, and it is fair to suspect that holiday observance is going to
> reduce attendance (at the very least, in the later afternoon).
I assume that there is no way to change the date for *this* conference;
[EMAIL PROTECTED] (Donald Bruce Stewart) wrote:
> The two where nhc98 wins are due to nhc98 producing the wrong output.
> The testsuite doesn't diff the output yet..
Only one of those gives the wrong output (spectral/integer). The other
(spectral/calendar) looks right to me.
Interestingly, when
On Thu, 22 Feb 2007, Seth Gordon wrote:
TFP 2007 wrote:
Dear Colleagues,
You may now resgister for TFP 2007! TFP 2007 will be held April 2-4,
2007 in New York City, USA.
Aaargh!
April 2 is the first night of Passover. This is not one of those
obscure holidays whose names are Hebrew f
TFP 2007 wrote:
>
> Dear Colleagues,
>
> You may now resgister for TFP 2007! TFP 2007 will be held April 2-4,
> 2007 in New York City, USA.
Aaargh!
April 2 is the first night of Passover. This is not one of those
obscure holidays whose names are Hebrew for "alternate-side parking
suspended"[*]
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:
primes :: [Integer]
primes = primesFilter 1 [2..]
primesFilter :: Integer -> [Integer] -> [Integer]
primesFilter primorial (n:ns)
| (gcd prim
Hello,
I need to interact with some other program, and wrote the following code:
module Main where
import System.Process
import System.IO
main :: IO ()
main = do
putStrLn "Running proc9..."
(inp,out,err,pid) <- runInteractiveProcess "prog1" [] Nothing Nothing
hSetBufferin
Henning Thielemann wrote:
>> In other words, 'Query a' just assembles a valid SQL-string,
>> it does not query or execute anything.
>
> Of course, instead of the DSEL approach "don't execute anything, only
> construct a program in a foreign language which does that" it would be
> nice to have a da
On Wed, 21 Feb 2007 [EMAIL PROTECTED] wrote:
> Albert Y. C. Lai wrote:
> > [EMAIL PROTECTED] wrote:
> >> Albert Y. C. Lai wrote:
> >>
> >>> If and only if the database is a purely functional immutable data
> >>> structure, this can be done. [...]
> >>> Many interesting databases are not purely fu
> The problem is that when the main thread ends, the RTS doesn't stop
> for another 6 or so seconds. The only thread that runs this long is
> the handler (waitFor (secs 8.0)) but it has already been killed. So
> I'm scratching my head a bit.
Short answer: use -threaded.
The runtime is waiting fo
Hi Chad,
I think this idea is better than what I had suggested, but as it
stands it doesn't typecheck. Did you mean something like this?
Yep, just the type signature was wrong :)
leaves :: Tree -> [Int]
leaves = f []
where
f rest (Leaf n) = n : rest
f rest (Branch l r) = f (f r
Tom Hawkins wrote:
> Any recommendations for speeding up extracting the set of leaves from a
> tree?
>
> data Tree = Branch Tree Tree | Leaf Int deriving (Eq, Ord)
>
> My slow, naive function:
>
> leaves :: Tree -> Set Int
> leaves (Leaf n) = singleton n
> leaves (Branch left right) = union (lea
Tom Hawkins wrote:
Any recommendations for speeding up extracting
the set of leaves from a tree?
Tom,
The standard library already has this, in Data.Tree
and Data.Foldable.toList.
I'm interested to know how well that performs compared
to the roll-your-own solutions proposed so far in this
thr
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
Hello!
I have a problem with overlapping instances for which I already know a
workaround. However, I'm still curious to know if there isn't a simpler solution
available. I have a feeling that -fallow-incoherent-instances might be the
answer, but I can't get it to work.
In the code at the end
Alistair Bayley wrote:
Below is a test case for a threading problem I can't figure out. It
models a socket server (here I've replaced the socket with an MVar, to
keep it simple). The idea is to have a listener which accepts incoming
requests on the socket. When one arrives, it forks a handler thr
Below is a test case for a threading problem I can't figure out. It
models a socket server (here I've replaced the socket with an MVar, to
keep it simple). The idea is to have a listener which accepts incoming
requests on the socket. When one arrives, it forks a handler thread to
deal with the req
29 matches
Mail list logo