Re: [Haskell-cafe] Disadvantages of de Bruijn indicies?

2007-05-14 Thread Nils Anders Danielsson
On Sun, 13 May 2007, Stefan Holdermans [EMAIL PROTECTED] wrote: Anyway, Conor and James' Haskell Workshop paper on manipulating syntax that involves both free and bound variables [1] is really nice and could perhaps be of interest to you. If I remember correctly this paper is not about a pure

Re: [Haskell-cafe] Disadvantages of de Bruijn indicies?

2007-05-14 Thread Stefan Holdermans
Nils, Anyway, Conor and James' Haskell Workshop paper on manipulating syntax that involves both free and bound variables [1] is really nice and could perhaps be of interest to you. If I remember correctly this paper is not about a pure de Bruijn index representation, but about a mix between

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Andrew Coppin
Stefan Holdermans wrote: This is rather typical in the field of program analysis. Getting the analysis precise is impossible and reduces to solving the halting problem. So, the next best thing is to get an approximate answer. An import design guideline to such an analysis is to err on the safe

[Haskell-cafe] More mystery with existentials and fundeps

2007-05-14 Thread Matthew Sackman
Hi, {-# OPTIONS_GHC -fglasgow-exts #-} class F a b | b - a where data G :: * - * where GC :: (F a b) = a - G b foo :: (F a b) = G b - a foo g = case g of (GC a) - a I may be being dumb, but I think this should work. Any value of G using the GC constructor will be

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Stefan Holdermans
Andrew, Right. So what you're saying is that for most program properties, you can partition the set of all possible problems into the set for which X is true, the set for which X is false, and a final set for programs where we can't actually determine the truth of X. Is that about right?

[Haskell-cafe] CUFP website

2007-05-14 Thread Cyril Schmidt
I noticed recently that the website of CUFP conference (Commercial Uses of Function Programming), which used to be at http://www.galois.com/cufp, is not accessible anymore. Does anybody know where it moved? Cyril ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Disadvantages of de Bruijn indicies?

2007-05-14 Thread Claus Reinke
Anyway, Conor and James' Haskell Workshop paper on manipulating syntax that involves both free and bound variables [1] is really nice and could perhaps be of interest to you. If I remember correctly this paper is not about a pure de Bruijn index representation, but about a mix between names and

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Andrew Coppin wrote: Right. So what you're saying is that for most program properties, you can partition the set of all possible problems into the set for which X is true, the set for which X is false, and a final set for programs where we can't actually determine the truth of X. Is that about

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-14 Thread Henning Thielemann
On Fri, 11 May 2007, Malcolm Wallace wrote: *Text.ParserCombinators.PolyLazy runParser (exactly 4 (satisfy Char.isAlpha)) (abc104++undefined) (*** Exception: Parse.satisfy: failed This output is exactly correct. You asked for the first four characters provided that they were

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Christopher L Conway
On 5/14/07, Roberto Zunino [EMAIL PROTECTED] wrote: Also, using only rank-1: polyf :: Int - a - Int polyf x y = if x==0 then 0 else if x==1 then polyf (x-1) (\z-z) else polyf (x-2) 3 Here passing both 3 and (\z-z) as y confuses the type inference. Actually, I tried

[Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread Christopher L Conway
I am new to Haskell---and also to languages with the off-side rule--and working my way through Hal Daume's tutorial. I'm a little confused by the support for code layout in Emacs' haskell-mode. Is it buggy, or am I doing something wrong. For example, here's the Hello, world example from the

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-14 Thread Malcolm Wallace
Henning Thielemann [EMAIL PROTECTED] wrote: *Text.ParserCombinators.PolyLazy runParser (exactly 4 (satisfy Char.isAlpha)) (abc104++undefined) (*** Exception: Parse.satisfy: failed How can I rewrite the above example that it returns (abc*** Exception: Parse.satisfy:

[Haskell-cafe] Re: More mystery with existentials and fundeps

2007-05-14 Thread Matthew Sackman
On Mon, May 14, 2007 at 12:47:02PM +0100, Matthew Sackman wrote: {-# OPTIONS_GHC -fglasgow-exts #-} class F a b | b - a where data G :: * - * where GC :: (F a b) = a - G b foo :: (F a b) = G b - a foo g = case g of (GC a) - a And just to confirm, this is

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Jules Bean
Christopher L Conway wrote: The inference assigns y the type (t1 - t1) even though it is assigned the value 3? Yes, because type classes are open, and maybe you will demonstrate some way to make t1-t1 an instance of Num. Note the Num (t1 - t1) constraint in the type...

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-14 Thread Henning Thielemann
On Mon, 14 May 2007, Malcolm Wallace wrote: Perhaps I should just rewrite the 'exactly' combinator to have the behaviour you desire? Its current definition is: exactly 0 p = return [] exactly n p = do x - p xs - exactly (n-1) p return

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Matthew Brecknell
Roberto Zunino: Here passing both 3 and (\z-z) as y confuses the type inference. Christopher L Conway: polyf :: forall a t1 t. (Num (t1 - t1), Num a, Num t) = a - (t1 - t1) - t The inference assigns y the type (t1 - t1) even though it is assigned the value 3? Almost. It assigns y the

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Christopher L Conway wrote: On 5/14/07, Roberto Zunino [EMAIL PROTECTED] wrote: Also, using only rank-1: polyf :: Int - a - Int polyf x y = if x==0 then 0 else if x==1 then polyf (x-1) (\z-z) else polyf (x-2) 3 Here passing both 3 and (\z-z) as y confuses the type

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-14 Thread Henning Thielemann
On Mon, 14 May 2007, Malcolm Wallace wrote: Essentially, you need to return a constructor as soon as you know that the initial portion of parsed data is correct. Often the only sensible way to do that is to use the 'apply' combinator (as shown in the examples above), returning a constructor

[Haskell-cafe] CUFP

2007-05-14 Thread Simon Peyton-Jones
The CUFP website is working again now. http://cufp.galois.com/ Thanks for pointing it out. Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Matthew Brecknell wrote: Roberto Zunino: Here passing both 3 and (\z-z) as y confuses the type inference. So the type inference is not really confused at all. It just gives a not-very-useful type. Yes, you are right, I didn't want to involve type classes and assumed 3::Int. A better

[Haskell-cafe] Re: How to decrease ghc link time

2007-05-14 Thread Simon Marlow
Georg Sauthoff wrote: Simon Marlow [EMAIL PROTECTED] wrote: Hi, Georg Sauthoff wrote: I am a bit unhappy with the link time of the project (i.e. the time ghc needs to link everyting). The project consinst of ~60 Haskell and ~25 foreign files. [..] Make sure everything being linked is on

Re: [Haskell-cafe] Lazy HTML parsing with HXT, HaXML/polyparse, what else?

2007-05-14 Thread Malcolm Wallace
Henning Thielemann [EMAIL PROTECTED] wrote: exactly 0 p = return [] exactly n p = do x - p xs - exactly (n-1) p return (x:xs) Is there a difference between 'exactly' and 'replicateM' ? With this definition, clearly not. But when

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread Nick Meyer
Hi Christopher, I have also noticed that haskell-mode (and indeed Haskell) can be finicky sometimes. I usually put module [Name] where all on the same line and leave imports on the left margin, so I hadn't experienced the first problem you mentioned. However, I do notice that if I re-arrange

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread David House
On 14/05/07, Christopher L Conway [EMAIL PROTECTED] wrote: For example, here's the Hello, world example from the tutorial, with the indentation induced by pounding Tab in haskell-mode. test.hs: module Test where import IO main = do putStrLn Hello, world Prelude :l test [1 of 1]

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread Christopher L Conway
On 5/14/07, David House [EMAIL PROTECTED] wrote: You should install 2.3 from the haskell-mode page [1]. Isaac Jones, maintainer of the Debian haskell-mode package has been contacted in order to get the latest version in the Debian repository, so it should happen soon, but in the mean time you

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread Roberto Zunino
Nick Meyer wrote: main = do putStrLn Enter a number: inp - getLine let n = read inp if n == 0 then putStrLn Zero else putStrLn NotZero (that's with all the expressions in the do block lining up vertically, if that doesn't show up in a fixed-width

[Haskell-cafe] Re: ANNOUNCE: Harpy -- run-time code generation library

2007-05-14 Thread apfelmus
[Relocated to haskell-cafe] Dirk Kleeblatt wrote: apfelmus wrote: Note that even currently, your operations cannot be strict in the address a label refers to because this may be determined later than the first use of the label. In other words, your example code fac = do [...] (1) jmp

[Haskell-cafe] instance monad problem

2007-05-14 Thread Veer Singh
Hello, I am trying to learn haskell , but i am struggling with types , its been around 7 days , it will be very kind if some explain it why this error , i think this is the only stumbling block . I am looking for the comparison on why similar code works , while other code not . I get this

Re: [Haskell-cafe] instance monad problem

2007-05-14 Thread Creighton Hogg
Hi On 5/14/07, Veer Singh [EMAIL PROTECTED] wrote: Hello, I am trying to learn haskell , but i am struggling with types , its been around 7 days , it will be very kind if some explain it why this error , i think this is the only stumbling block . I am looking for the comparison on why similar

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Matthew Brecknell
Roberto Zunino: Yes, you are right, I didn't want to involve type classes and assumed 3::Int. A better example would be: polyf :: Int - a - Int polyf x y = if x==0 then 0 else if x==1 then polyf (x-1) (\z-z) else polyf (x-2) () Here, passing both () and (\z-z)

Re: [Haskell-cafe] instance monad problem

2007-05-14 Thread Stefan Holdermans
Veer, I get this error on ghci : {- `a' is not applied to enough type arguments Expected kind `*', but `a' has kind `* - *' In the type `SS a' In the type `(Monad a) = {Monad (SS a)}' In the instance declaration for `Monad (SS a)' -} So, what you are running into is not as much a