[Haskell-cafe] nobench: now with hbc support (!)

2007-02-20 Thread Donald Bruce Stewart
Just a quick note. I've tweaked the benchmarks some more, adding support for Lennart's hbc compiler. (Go hbc!). Also, we have nice html output (thanks to Text.XHtml!). http://www.cse.unsw.edu.au/~dons/nobench/results.html Pretty :-) Remaining tasks left are to port the rest of the 'real' ca

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

2007-02-20 Thread Gene A
On 2/10/07, Peter Berry <[EMAIL PROTECTED]> wrote: Sigh, I seem to have done a reply to sender. Reposting to the list. On 06/02/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > Hello, > > I would like to create a Haskell function that generates a truth table, for > all Boolean values, say, us

[Haskell-cafe] Call for testers: using Cabal to build RPMs

2007-02-20 Thread Bryan O'Sullivan
I've got a branch of Cabal that adds a new command, "rpm", that lets you build an RPM package with a single invocation: runhaskell Setup.*hs rpm I've tested this pretty extensively with GHC 6.6, and I'm quite happy with it, but if there are other users of RPM-based distros out there, I'd ap

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

2007-02-20 Thread Nicolas Frisby
Here comes an overwhelming post (so stop here if you're not interested in applicative functors), but apfelmus stepped in this direction. The funny part is that, modulo dictionary passing (which might be compiled away), all 6 functions below do the Exact Same Thing because of newtype erasure (Calli

Re: [Haskell-cafe] Haskell School of Expression

2007-02-20 Thread Albert Y. C. Lai
Andrew Wagner wrote: Has anyone worked through HSOE lately? I'm wondering if I'm going to be able to work through the examples that use their graphic library, under gtk2hs on fedora. Is there a workaround for this? Just use module Graphics.SOE from package HGL. For example GHC comes with it. T

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

2007-02-20 Thread David House
On 20/02/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: It's also known as sequence :: Monad m => [m b] -> m [b] with m = (->) a Don't forget to import Control.Monad.Instances for this to work. -- -David House, [EMAIL PROTECTED] ___ Haskell-Caf

[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread apfelmus
Jens Blanck wrote: >> >> The point about "Eratosthenes's sieve" is that it does not specify >> algorithmically how to find the next number to be crossed. It does not >> even define how to store (crossed) numbers, it stores them "on paper". > > But , I believe that Eratosthenes's sieve does specify

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

2007-02-20 Thread apfelmus
Paul Moore wrote: > I'm after a function, sort of equivalent to map, but rather than > mapping a function over a list of arguments, I want to map a list of > functions over the same argument. The signature would be [a -> b] -> a > -> [b], but hoogle didn't come up with anything. > > It seems like

[Haskell-cafe] Re: speeding up fibonacci with memoizing

2007-02-20 Thread Jón Fairbairn
"Thomas Hartman" <[EMAIL PROTECTED]> writes: -> I just thought this was interesting, so I would share it. -> -- versus, try memoized_fibs !! 1 -> memoized_fibs = map memoized_fib [1..] -> memoized_fib = ((map fib' [0 ..]) !!) -> where -> fib' 0 = 0 -> fib' 1 = 1 -> fib'

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

2007-02-20 Thread Paul Moore
On 20/02/07, David Roundy <[EMAIL PROTECTED]> wrote: It's rather a small function to bother putting in the libraries, and I think better expressed using map directly: rmap fs x = map ($ x) fs Yes. Now that I know the idiom, there's clearly little point in having a named function for it. Thank

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

2007-02-20 Thread David Roundy
On Tue, Feb 20, 2007 at 02:07:08PM +, Paul Moore wrote: > I'm after a function, sort of equivalent to map, but rather than > mapping a function over a list of arguments, I want to map a list of > functions over the same argument. The signature would be [a -> b] -> a > -> [b], but hoogle didn't

Re: [Haskell-cafe] newbie question about denotational semantics

2007-02-20 Thread Nicolas Frisby
[my mail program hiccuped and chopped my message, sorry] 2 Another example that helped me when getting a feel for reasoning about monadic code (which is the basis of what we're doing here) was William Harrison's "Proof Abstraction for Imperative Languages". It uses monads and some of the notions

[Haskell-cafe] Haskell School of Expression

2007-02-20 Thread Andrew Wagner
Has anyone worked through HSOE lately? I'm wondering if I'm going to be able to work through the examples that use their graphic library, under gtk2hs on fedora. Is there a workaround for this? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http:

Re: [Haskell-cafe] newbie question about denotational semantics

2007-02-20 Thread Nicolas Frisby
I'm still getting my head around this myself, but I know a few references that might help (maybe not directly, but they're in the ballpark). 1 I believe the phrase "natural lifting" or "naturality of liftings" is what you're after when you attempt to compare a monad and a "bigger monad" that incl

[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread Jens Blanck
The point about "Eratosthenes's sieve" is that it does not specify algorithmically how to find the next number to be crossed. It does not even define how to store (crossed) numbers, it stores them "on paper". But , I believe that Eratosthenes's sieve does specify how to store numbers and how t

Re: [Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimizationfun]

2007-02-20 Thread Claus Reinke
i have to say that i find the folklore sieve quite acceptable as a sieve, whereas the faster test-against-primes is obviously different. but the discussion has prompted me to write yet another sieve, perhaps more acceptable to purists. instead of using (mod p) repeatedly and filtering directl

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

2007-02-20 Thread Dougal Stanton
Quoth Paul Moore, nevermore, > >Prelude> map ($ 3) [(*2),(+1),div 1] > >[6,4,0] > > Cool. I told you I was missing something! :-) I suppose this would fit your original idea if you wanted that particular type signature. (Warning: not tested.) > f :: a -> [a -> b] -> [b] > f c fs = map ($ c) fs >

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

2007-02-20 Thread Paul Moore
On 20/02/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote: p.f.moore: > I'm after a function, sort of equivalent to map, but rather than > mapping a function over a list of arguments, I want to map a list of > functions over the same argument. The signature would be [a -> b] -> a > -> [b], but

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

2007-02-20 Thread Donald Bruce Stewart
p.f.moore: > I'm after a function, sort of equivalent to map, but rather than > mapping a function over a list of arguments, I want to map a list of > functions over the same argument. The signature would be [a -> b] -> a > -> [b], but hoogle didn't come up with anything. Prelude> map ($ 3) [(*2),

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

2007-02-20 Thread Paul Moore
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything. It seems like an obvious analogue of map, s

[Haskell-cafe] newbie question about denotational semantics

2007-02-20 Thread Alexander Vodomerov
Hi all! I'm just started learning denotational semantics and have a simple question. Suppose, we have simple language L (e.g. some form of lambda-calculus) and have a semantic function: E : Term_L -> Value. Now, suppose, we extended our language with some additional side-effects (e.g. state o

Re: [Haskell-cafe] return?

2007-02-20 Thread Bulat Ziganshin
Hello Vikrant, Tuesday, February 20, 2007, 10:59:16 AM, you wrote: > I encounter situation in which my function has to end recursion by > doing "nothing" and otherwise keep calling same function with some > different parameters. I did not find anything equivalent to "pass" > or "return" statement

Re: [Haskell-cafe] trouble installing ghc 6.6: xargs: /usr/bin/ar: terminated by signal 11

2007-02-20 Thread Daniil Elovkov
Hello cmm.h seems to sit in TOPDIR/includes In the makefile these lines are close SplitObjs=NO H_FILES = $(wildcard ../includes/*.h) $(wildcard *.h) Maybe you accidentally did something with the second while editing the first. 2007/2/20, Thomas Hartman <[EMAIL PROTECTED]>: I finally got ar

Re[2]: [Haskell-cafe] ANNOUNCE: nobench: Haskell implementaion benchmarks. GHC v Hugs v Yhc v NHC v ...

2007-02-20 Thread Bulat Ziganshin
Hello Dougal, Monday, February 19, 2007, 3:02:30 PM, you wrote: > I suppose the ideal way to do it would be benchmarks for the (1) idiomatic > and (2) the highly tuned implementations. Then the compiler writers can > push 1 towards 2, while the pesky shootout implementers can move the > goalposts

[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread apfelmus
Yitzchak Gale wrote: > Melissa O'Neill wrote: >>- Eratosthenes's sieve never says the equivalent of, "Hmm, I >> wonder if 19 is a multiple of 17" -- but both the basic "sieve" we >> began with and the deleteOrd version do > > So then maybe I taught my daughter the wrong thing. > When she does

Re: [Haskell-cafe] trouble installing ghc 6.6: xargs: /usr/bin/ar: terminated by signal 11

2007-02-20 Thread Thomas Hartman
I finally got around to trying this, but still no luck. now getting missing cmm.h error. [EMAIL PROTECTED]:~/haskellInstalls/ghc-6.6$ cat mk/build.mk SplitObjs=NO after doing sudo make > make.out [EMAIL PROTECTED]:~/haskellInstalls/ghc-6.6$ tail make.out -

Re: [Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread Yitzchak Gale
Hi Melissa, You wrote: - Eratosthenes's sieve never says the equivalent of, "Hmm, I wonder if 19 is a multiple of 17" -- but both the basic "sieve" we began with and the deleteOrd version do So then maybe I taught my daughter the wrong thing. When she does 17, she moves ahead one number at

Re: [Haskell-cafe] return?

2007-02-20 Thread Donald Bruce Stewart
vikrant.patil: > >Hi, >I am writing a recursive function which does some IO >operation. I encounter situation in which my function has to >end recursion by doing "nothing" and otherwise keep calling >same function with some different parameters. I did not find >anything