Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Ketil Malde
Don Stewart [EMAIL PROTECTED] writes: goalieca: So in a few years time when GHC has matured we can expect performance to be on par with current Clean? So Clean is a good approximation to peak performance? If I remember the numbers, Clean is pretty close to C for most benchmarks, so

Re[2]: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Bulat Ziganshin
Hello Lennart, Thursday, November 1, 2007, 2:45:49 AM, you wrote: But yeah, a code generator at run time is a very cool idea, and one that has been studied, but not enough. vm-based languages (java, c#) has runtimes that compile bytecode to the native code at runtime -- Best regards, Bulat

RE: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Simon Peyton-Jones
Yes, that's right. We'll be doing a lot more work on the code generator in the rest of this year and 2008. Here we includes Norman Ramsey and John Dias, as well as past interns Michael Adams and Ben Lippmeier, so we have real muscle! Simon | I don't think the register allocater is being

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Rodrigo Queiro
I assume the reason the switched away from LOC is to prevent programmers artificially reducing their LOC count, e.g. by using a = 5; b = 6; rather than a = 5; b = 6; in languages where newlines aren't syntactically significant. When gzipped, I guess that the ;\n string will be represented about

Re: [Haskell-cafe] Haskell libraries for computer vision

2007-11-01 Thread Alberto Ruiz
I have included in the web page a reference to this earlier work, in which all the key ideas were already present. For example, using ordinary Haskell functions to process an infinite list containing the whole image sequence taken by the camera... We can write extremely concise and powerful

[Haskell-cafe] virtual lambda

2007-11-01 Thread Alberto Ruiz
Hi, I think that you may like the following demo of a simple computer vision application powered by Haskell: http://covector.blogspot.com/2007/10/functional-augmented-reality.html Alberto ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Stefan Holdermans
Bernie wrote: I discussed this with Rinus Plasmeijer (chief designer of Clean) a couple of years ago, and if I remember correctly, he said that the native code generator in Clean was very good, and a significant reason why Clean produces (relatively) fast executables. I think he said

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Stefan Holdermans
Neil wrote: The Clean and Haskell languages both reduce to pretty much the same Core language, with pretty much the same type system, once you get down to it - so I don't think the difference between the performance is a language thing, but it is a compiler thing. The uniqueness type stuff may

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Paulo J. Matos
On 01/11/2007, Simon Peyton-Jones [EMAIL PROTECTED] wrote: Yes, that's right. We'll be doing a lot more work on the code generator in the rest of this year and 2008. Here we includes Norman Ramsey and John Dias, as well as past interns Michael Adams and Ben Lippmeier, so we have real

RE: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Simon Peyton-Jones
http://hackage.haskell.org/trac/ghc/wiki/Commentary | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Paulo J. Matos | Sent: 01 November 2007 13:42 | To: Simon Peyton-Jones | Cc: Neil Mitchell; Stefan O'Rear; [EMAIL PROTECTED]; haskell-cafe@haskell.org

[Haskell-cafe] Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-01 Thread apfelmus
Stefan Holdermans wrote: Exposing uniqueness types is, in that sense, just an alternative to monadic encapsulation of side effects. While *World - (a, *World) seems to work in practice, I wonder what its (denotational) semantics are. I mean, the two programs loop, loop' :: *World -

Re: [Haskell-cafe] Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-01 Thread Arnar Birgisson
Hi there, I'm new here, so sorry if I'm stating the obvious. On Nov 1, 2007 2:46 PM, apfelmus [EMAIL PROTECTED] wrote: Stefan Holdermans wrote: Exposing uniqueness types is, in that sense, just an alternative to monadic encapsulation of side effects. While *World - (a, *World) seems to

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Bryan O'Sullivan
Ketil Malde wrote: Python used to do pretty well here compared to Haskell, with rather efficient hashes and text parsing, although I suspect ByteString IO and other optimizations may have changed that now. It still does just fine. For typical munge a file with regexps, lists, and maps

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Justin Bailey
On 10/31/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I didn't keep a copy, but if someone wants to retrieve it from the Google cache and put it on the new wiki (under the new licence, of course), please do so. Cheers, Andrew Bromage Done:

[Haskell-cafe] do/if/then/else confusion

2007-11-01 Thread David Carter
Another newbie question, but I can't seem to find any answers on the web... Can someone tell me what's wrong with this? import qualified System.Posix.Directory as PD readdirAll :: PD.DirStream - IO [String] readdirAll d = do dir - PD.readDirStream d if dir == then return []

Re: [Haskell-cafe] do/if/then/else confusion

2007-11-01 Thread Brandon S. Allbery KF8NH
On Nov 1, 2007, at 13:47 , David Carter wrote: else rest - readdirAll d You need another do here to use the - syntax. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED] system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED] electrical and

[Haskell-cafe] Re: do/if/then/else confusion

2007-11-01 Thread David Carter
David Carter wrote: Another newbie question, but I can't seem to find any answers on the web... Just figured it out myself ... I need a do after the else, of course. (But I still think the error message is less than helpful!). Sorry for the bandwidth David Can someone tell me what's

[Haskell-cafe] Slightly off-topic

2007-11-01 Thread PR Stanley
Hi folks Apologies for the off-topic post. If anyone knows anything about the rules of proof by deduction and quantifiers I'd be grateful for some assistance. Much obliged, Paul ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Slightly off-topic

2007-11-01 Thread Don Stewart
prstanley: Hi folks Apologies for the off-topic post. If anyone knows anything about the rules of proof by deduction and quantifiers I'd be grateful for some assistance. Much obliged, http://www.cs.cmu.edu/~rwh/plbook/ Is an excellent introduction to reasoning about programming languages.

[Haskell-cafe] Regex API ideas

2007-11-01 Thread ChrisK
Hi Bryan, I wrote the current regex API, so your suggestions are interesting to me. The also goes for anyone else's regex API opinions, of course. Bryan O'Sullivan wrote: Ketil Malde wrote: Python used to do pretty well here compared to Haskell, with rather efficient hashes and text

[Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Jim Burton
I am trying to rewrite sentences in a logical language into DNF, and wonder if someone would point out where I'm going wrong. My dim understanding of it is that I need to move And and Not inwards and Or out, but the function below fails, for example: dnf (Or (And A B) (Or (And C D) E))

Re: [Haskell-cafe] Regex API ideas

2007-11-01 Thread Bryan O'Sullivan
ChrisK wrote: The Haskell regexp libraries actually give us something of a leg down with respect to Python and Perl. True, the pure Haskell library is not as fast as a C library. Actually, I wasn't referring to the performance of the libraries, merely to the non-stick nature of the API.

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
A good way to approach this is data-structure-driven programming. You want a data structure which represents, and can _only_ represent, propositions in DNF. So: data Term = Pos Var | Neg Var type Conj = [Term] type DNF = [Conj] Then write: dnf :: LS - DNF The inductive definition of dnf is

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Tim Newsham
Unfortunately, they replaced line counts with bytes of gzip'ed code -- while the former certainly has its problems, I simply cannot imagine what relevance the latter has (beyond hiding extreme amounts of repetitive boilerplate in certain languages). Sounds pretty fair to me. Programming is a

Re: [Haskell-cafe] Re: do/if/then/else confusion

2007-11-01 Thread Felipe Lessa
On 11/1/07, David Carter [EMAIL PROTECTED] wrote: (But I still think the error message is less than helpful!). Maybe a bug should be filled? -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Sebastian Sylvan
On 01/11/2007, Tim Newsham [EMAIL PROTECTED] wrote: Unfortunately, they replaced line counts with bytes of gzip'ed code -- while the former certainly has its problems, I simply cannot imagine what relevance the latter has (beyond hiding extreme amounts of repetitive boilerplate in certain

Re: [Haskell-cafe] Why can't Haskell be faster?

2007-11-01 Thread Hugh Perkins
On 10/31/07, Paulo J. Matos [EMAIL PROTECTED] wrote: Hello all, I, along with some friends, have been looking to Haskell lately. I'm very happy with Haskell as a language, however, a friend sent me the link: http://shootout.alioth.debian.org/gp4/ Careful: it's worse than you think. Many

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Christopher L Conway
Jim, Lukes suggestion is a good one, and should help focus you on the syntactic constraints of DNF. A property that your dnf function should have is that the right-hand side of each case should yield a DNF formula. Take, for example, dnf (And s1 s2) = And (dnf s1) (dnf s2) Does And'ing

Re: Re[2]: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread Lennart Augustsson
Yes, of course. But they don't do partial evaluation. On 11/1/07, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello Lennart, Thursday, November 1, 2007, 2:45:49 AM, you wrote: But yeah, a code generator at run time is a very cool idea, and one that has been studied, but not enough.

Re: [Haskell-cafe] Re: Hiding side effects in a data structure

2007-11-01 Thread Hugh Perkins
On 10/26/07, John Meacham [EMAIL PROTECTED] wrote: Heh, the plethora of pdf papers on Haskell is part of what originally brought me to respect it. Something about that metafont painted cmr just makes me giddy as a grad student. A beautifully rendered type inference table is a masterful work of

Re: [Haskell-cafe] Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-01 Thread Paul Hudak
One can certainly use an operational semantics such as bisimulation, but you don't have to abandon denotational semantics. The trick is to make output part of the "final answer". For a conventional imperative language one could define, for example, a (lifted, recursive) domain: Answer =

[Haskell-cafe] Re: Hiding side effects in a data structure

2007-11-01 Thread Jon Fairbairn
Hugh Perkins [EMAIL PROTECTED] writes: On 10/26/07, John Meacham [EMAIL PROTECTED] wrote: Heh, the plethora of pdf papers on Haskell is part of what originally brought me to respect it. Something about that metafont painted cmr just makes me giddy as a grad student. A beautifully rendered

Re: [Haskell-cafe] do/if/then/else confusion

2007-11-01 Thread Jules Bean
David Carter wrote: readdirAll :: PD.DirStream - IO [String] readdirAll d = do dir - PD.readDirStream d if dir == then return [] else rest - readdirAll d return (dir:rest) Compiling with GHC 6.6.1 gives me the not-very-useful message Parse error in pattern,

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Jules Bean
It's much much easier to work with n-ary than binary. It's also easier to define disjunctive normal form by mutual recursion with conjunctive normal form. Jules ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Hiding side effects in a data structure

2007-11-01 Thread Jonathan Cast
On Thu, 2007-11-01 at 21:42 +, Jon Fairbairn wrote: Hugh Perkins [EMAIL PROTECTED] writes: On 10/26/07, John Meacham [EMAIL PROTECTED] wrote: Heh, the plethora of pdf papers on Haskell is part of what originally brought me to respect it. Something about that metafont painted cmr

Re: [Haskell-cafe] Re: Hiding side effects in a data structure

2007-11-01 Thread Cale Gibbard
On 21/10/2007, Jon Fairbairn [EMAIL PROTECTED] wrote: No, they (or at least links to them) typically are that bad! Mind you, as far as fragment identification is concerned, so are a lot of html pages. But even if the links do have fragment ids, pdfs still impose a significant overhead: I

[Haskell-cafe] Is there a module for multivariate linear regression?

2007-11-01 Thread Lihn, Steve
I am looking for a Haskell module that will do multivariate linear regression. Does someone know which module will do it? That is, the equivalent of Perl's Statistics::Regression.pm. http://search.cpan.org/~itub/PerlMol-0.35_00.ppm/lib/Statistics/Regression.pm Thanks, Steve

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Arnar Birgisson
Hey folks, On Nov 1, 2007 6:41 PM, Luke Palmer [EMAIL PROTECTED] wrote: A good way to approach this is data-structure-driven programming. You want a data structure which represents, and can _only_ represent, propositions in DNF. So: data Term = Pos Var | Neg Var type Conj = [Term] type

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/2/07, Luke Palmer [EMAIL PROTECTED] wrote: On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote: dnf :: LS - DNF dnf (Var s) = [[Pos s]] dnf (Or l1 l2) = (dnf l1) ++ (dnf l2) dnf (And l1 l2) = [t1 ++ t2 | t1 - dnf l1, t2 - dnf l2] dnf (Not (Not d)) = dnf d dnf (Not (And l1 l2)) =

Re: [Haskell-cafe] Disjunctive Normal Form

2007-11-01 Thread Luke Palmer
On 11/1/07, Arnar Birgisson [EMAIL PROTECTED] wrote: I'm learning too and found this an interesting problem. Luke, is this similar to what you meant? Heh, your program is almost identical to the one I wrote to make sure I wasn't on crack. :-) data LS = Var String | Not LS | And LS LS | Or LS

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-11-01 Thread ajb
Quoting Justin Bailey [EMAIL PROTECTED]: Done: http://www.haskell.org/haskellwiki/RuntimeCompilation . Please update it as needed. Thanks! Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Need help from a newby

2007-11-01 Thread karle
My declaration is as followed:- type Address = Int data Port = C | D deriving(Eq,Show) data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) data Pkgtype = RTD | U deriving(Eq,Show) type Pkg = (Pkgtype,Address,Payload) type Table = [(Address,Port)]

[Haskell-cafe] Re: Need help from a newby

2007-11-01 Thread ChrisK
karle wrote: My declaration is as followed:- type Address = Int data Port = C | D deriving(Eq,Show) data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) data Pkgtype = RTD | U deriving(Eq,Show) type Pkg = (Pkgtype,Address,Payload) type Table = [(Address,Port)]

Re: [Haskell-cafe] Need help from a newby

2007-11-01 Thread karle
ChrisK-3 wrote: karle wrote: My declaration is as followed:- type Address = Int data Port = C | D deriving(Eq,Show) data Payload = UP[Char] | RTDP(Address,Port) deriving(Eq,Show) data Pkgtype = RTD | U deriving(Eq,Show) type Pkg = (Pkgtype,Address,Payload) type Table =

Re: [Haskell-cafe] Need help from a newby

2007-11-01 Thread Christopher L Conway
Substitute the definition of type Table into the error: Type error in explicitly typed binding *** Term : [(a,p)] *** Type : [(a,b)] *** Does not match : [Table] where [Table] = [[(Address,Port)]] Do you see why the expression [ (a,p) ] cannot have type [ [ (Address, Port)

[Haskell-cafe] Re: do/if/then/else confusion

2007-11-01 Thread Maurí­cio
(...) Can someone tell me what's wrong with this? import qualified System.Posix.Directory as PD readdirAll :: PD.DirStream - IO [String] readdirAll d = do dir - PD.readDirStream d if dir == then return [] else rest - readdirAll d return (dir:rest)