RE: GHC lazy eval optimization bug

2008-02-05 Thread Simon Peyton-Jones
| Thank you for the explanation. Inlining does explain the behavior I | was seeing, and -fno-state-hack does make the program behave the way | I'd expect. | | I would like to humbly submit that perhaps this optimization should be | off by default. I agree that the current behaviour sometimes

RE: Will implicit parameters survive?

2008-02-07 Thread Simon Peyton-Jones
I don't have any active plans to remove implicit parameters. I think they are not heavily used, but for those that do use them they seem to be quite helpful, and (important for me) their effect on the compiler is quite localised, so they cause little trouble. Still, I'm always interested to

RE: Shared Libraries in ghci

2008-02-08 Thread Simon Peyton-Jones
Any chance of documenting your experience on the GHC user documentation page? http://haskell.org/haskellwiki/GHC (under collaborative documentation) A kind of how-to that worked for you, with pointers to relevant manual parts etc. Simon | -Original Message- | From: [EMAIL

RE: static constants -- ideas?

2008-02-25 Thread Simon Peyton-Jones
| On another note, I am extremely curious about the difference | between statically compiling a list and building it at | runtime. I find it hard to wrap my head around the fact that I | can build the list at runtime in a short time, but can not | compile it without eating all of my

RE: STM and fairness

2008-02-29 Thread Simon Peyton-Jones
| I'd like to know a bit about the STM implementation in GHC, | specifically about how it tries to achieve fairness. I've been reading | Composable Memory Transactions but it does not contain that much | details on this specific matter. What I want to know boils down to | this: what order are

RE: monomorphic or not?

2008-03-06 Thread Simon Peyton-Jones
No, it's fine. compress is indeed monomorphic, but since it's called at exactly one type, namely Char, so it gets the monomorphic type [Char] - [Char]. That is what the Haskell Report says. (Or tries to.) Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]

RE: scope of header files

2008-03-06 Thread Simon Peyton-Jones
If, following this thread, you conclude that GHC should do something different than what it does, can you submit a Trac ticket? With a small example? Thanks S | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of | Duncan Coutts | Sent: 06 March 2008

RE: monomorphic or not?

2008-03-06 Thread Simon Peyton-Jones
| On Thu, Mar 06, 2008 at 08:56:15AM +, Simon Peyton-Jones wrote: | No, it's fine. compress is indeed monomorphic, but since it's called | at exactly one type, namely Char, so it gets the monomorphic type | [Char] - [Char]. That is what the Haskell Report says. (Or tries

RE: Optimization beyond the Module Border

2008-03-19 Thread Simon Peyton-Jones
| I have noticed that there is a great difference between optimizing | modules separately and all at once, e.g., with -fforce-recomp. I have | had examples factors up to 15 in run time (and even different behavior | in context with unsafePerformIO). GHC does a lot of cross-module inlining

RE: Optimization beyond the Module Border

2008-03-20 Thread Simon Peyton-Jones
| I'd be interested in any progress here -- we noticed issues with | optimisations in the stream fusion package across module boundaries | that we never tracked down. If there's some key things not firing, | that would be good to know. | | I suspect that if all modules are compiled -O0, then

RE: Optimization beyond the Module Border

2008-03-21 Thread Simon Peyton-Jones
| Would it be possible for the compiler to say something like: You are | applying level 2 optimization but some dependencies where compiled without | optimization enabled. To get full optimization, consider recompiling x,y,z | with -O2 - at least this would give us a fighting chance to 'fix'

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
| To use bar, you need (Ord a, Ord b). You're assuming that Ord (a, b) | implies that, but it's the other way round. | | Logically, the implication holds. There's an equivalence: | | Ord a /\ Ord b = Ord (a,b) | ... | The problem with dictionaries is that you have to store the

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
Why unfortunately? Looks fine to me. Simon | | Unfortunately, GHC accepts the following: | | {-# LANGUAGE FlexibleInstances #-} | module Foo2 where | | data Foo = Foo | deriving Eq | | instance Ord (Foo, Foo) where | (Foo, Foo) (Foo, Foo) = False

RE: flexible contexts and context reduction

2008-03-27 Thread Simon Peyton-Jones
dictionaries from an Ord (a,b) dictionary. (But not an Ord a or Ord b one.) S | | Ganesh | | -Original Message- | From: Simon Peyton-Jones [mailto:[EMAIL PROTECTED] | Sent: 27 March 2008 09:05 | To: Sittampalam, Ganesh; 'Tom Schrijvers'; Ganesh Sittampalam | Cc: glasgow-haskell-users

RE: simple CSE?

2008-04-01 Thread Simon Peyton-Jones
Not reliably, no. GHC's current CSE is rather opportunistic: we take the opportunity if it's presented in the form let x = e in let y = e in A proper CSE pass would be a nice, containable, project. Simon From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Conal Elliott Sent:

RE: [GHC] #2153: GHCi does not have a :source command to load further .ghci files

2008-04-07 Thread Simon Peyton-Jones
| Wow, that simple??? | | What needs to be done to get this in :? output? (It should be in the | manual, at least...) Indeed! But it's more application-note than user manual. Fortunately, we have a place for such material, namely GHC's collaborative documentation (a wiki)

RE: Using GHC API to generate STG

2008-04-15 Thread Simon Peyton-Jones
LNull is a constructor, so it has no definition in STG. How might it be defined? LNull = ??? Instead, the code generator takes the list of data types (TyCons) as well as the list of bindings. From the former it generates all the per-data-type goop, including info tables for its

RE: 6.8 unable to derive with higher-kinded variable (6.6 could)

2008-04-18 Thread Simon Peyton-Jones
| GHC 6.8 seems unable to derive (some?) instances for data types with | higher-kinded variables. GHC 6.6 manages these just fine. See below. | data T w = T (w Bool) deriving (Show) | data ID x = ID x deriving (Show) | main = print (T (ID False)) Look at the instance declaration you'd get

RE: Error Interpreting Main with API

2008-04-22 Thread Simon Peyton-Jones
| The GHC API is behaving just like --make: it links the program if you | have a Main module. To ask it not to link, you want to do the same as | '--make -c', which in the GHC API means setting the ghcLink field of | DynFlags to NoLink. | | Thanks, this has solved the problem I was having. I

RE: [Haskell] How to define tail function for Even/Odd GADT lists?

2008-04-24 Thread Simon Peyton-Jones
[Redirecting to ghc-users] You're right that tailList ought to work. There are at least two reasons that it doesn't. First, GHC does not have a robust implementation of GADTs + functional dependencies. The interaction is very tricky. So I tried re-expressing it using type families, thus:

RE: Unexpected lack of optimisation

2008-04-29 Thread Simon Peyton-Jones
Neil A nice example, but I think it's difficult to give systematic solution. * The 'retry' function is a join point, where two different conditional branches join up. * As you say, if 'retry' was inlined, all would be fine. But what if 'retry' was big? Then we'd get lots of code duplication,

RE: Optimisation of unpackCString#

2008-04-29 Thread Simon Peyton-Jones
| I could imagine adding two rules to the simplifier: | | case unpackCString# of == case [] of | case unpackCString# xyz of == case (C# 'x': unpackCString# yz) of ... | This goes back to an old gripe of mine actually -- we can't get | at the length of a C string literal at compile time either,

RE: Optimisation of unpackCString#

2008-04-29 Thread Simon Peyton-Jones
| PROPOSAL 1: Add the following rules to the simplifier: | |case unpackCString# of == case [] of |case unpackCString# xyz of == case (C# 'x': unpackCString# yz) of | | I've been wanting to have a go at hacking GHC for a while, and this | seems like a good candidate to start with. If

RE: Unexpected lack of optimisation

2008-04-29 Thread Simon Peyton-Jones
| {-# INLINE foo #-} | foo = large | | bar x = if x then res else res | where res = foo | | By putting an INLINE on foo I am able to persuade it to be inlined | into the binding of bar, but I can't then persuade it to be inlined at | the let expression. I'm not certain what you mean here. I

RE: Unexpected lack of optimisation

2008-04-30 Thread Simon Peyton-Jones
| It worked, with: | | {-# INLINE [1] begin1 #-} | {-# INLINE begin2 #-} | | I don't think this approach will compose particularly well, and in the | real case I was trying (not this reduced example) I don't think it | will work because there is some recursion and RULES involved. I'll | have

RE: Unexpected lack of optimisation

2008-04-30 Thread Simon Peyton-Jones
| The situation in Neil's code is almost identical, except that the | top-level case expression is on a value passed by environment, not by | function argument. Interesting thought. I think you're describing a possible extension to the SpecConstr transformation described in Call pattern

RE: Optimisation of unpackCString#

2008-04-30 Thread Simon Peyton-Jones
| One of my ideas was some RULES that expand: | | test x | neil `isPrefixOf` x = ... | | ned `isPrefixOf` x = ... You might want to be careful about this, because you could really get a *lot* of code this way. | Simon: I will email you in a couple of weeks to discuss it. Great,

RE: instance export decls

2008-05-01 Thread Simon Peyton-Jones
Indeed! I think it'd be good to allow type signatures, including instance signatures, in export lists module Foo( data T (f :: * - *), instance Functor f = Eq (T f), g :: T f - T f ) The first step is to evolve a well-worked-out design. I think that'd be a very

Warnings about unused variables or imports

2008-05-06 Thread Simon Peyton-Jones
[Moving to GHC users: this thread concerns GHC's warning messages about unused things.] | But there are a few other inconvenient behaviors related only to | warnings, for instance | | module A where | foo x = x | | module B(foo) where | import A | | module C (module A, module B) where | import A

RE: Performance: Faster to define a function writing out all arguments?

2008-05-13 Thread Simon Peyton-Jones
| Anyway, as I am still wondering why ghc creates different code for |returnP a = return a |returnP = return | | | Ah, now I rember this coming up before. | | Simon, is this a CAF issue? Or did it trigger the -fno-state-hack case? I'm not sure. A small example would be good. | I've

RE: laziness, memoization and inlining

2008-05-14 Thread Simon Peyton-Jones
Scott | I'm experiencing some undesirable performance behavior, I suspect from | inlining things that shouldn't be, defeating my memoization attempts. This is bad, very bad. I think Don is right. I believe the following is happening. In your main program you have do let mesh = memoMesh

RE: laziness, memoization and inlining

2008-05-15 Thread Simon Peyton-Jones
Dillard | Cc: Simon Peyton-Jones; Don Stewart; glasgow-haskell-users@haskell.org | Subject: Re: laziness, memoization and inlining | | Scott Dillard wrote: | Simon, Don, | | You're right. -fno-state-hack fixed it. I've opened a trac ticket. | Program and test data are there. | | http

RE: bug in 6.8.2?

2008-05-19 Thread Simon Peyton-Jones
| class BufferData a where | write :: OutStream - a - IO () | | there is writeAll procedure which uses this `write` and therefore | should be able to write any BufferData instance: | | writeAll receiveBuf sendBuf cleanup x = | bracket (create receiveBuf sendBuf cleanup) (closeOut) | (\buf

RE: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-05-30 Thread Simon Peyton-Jones
| main = print $ foldl' (+) 0 [1..] | | with | | foldl' f y xs = foldl' y xs | where foldl' y [] = y | foldl' y (x:xs) = foldl' (f y x) xs | | runs indefinitely with very little memory consumption, while | | foldl' f y [] = y | foldl' f y (x:xs) = foldl' f (f y x) xs | | rapidly

RE: GHC rewrite rules pragma

2008-05-30 Thread Simon Peyton-Jones
| This is the main wibble people forget when writing rules -- inlining. | In your example, 'gen' is so cheap, it is immediately | inlined, so it won't be available to match on in your rule. I'll add a note in the user manual about this. In general, GHC tries RULES before inlining. In this

RE: ANNOUNCE: GHC 6.8.3 Release Candidate

2008-06-02 Thread Simon Peyton-Jones
Interesting * I think it is a Bad Idea for an application to assume that the implementation of (f^n) will not multiply by 1. Implementations of numeric algorithms probably make all sorts of ill-documented assumptions about the algebraic properties of numeric operations * On the other

RE: Having trouble with parallel Haskell

2008-06-05 Thread Simon Peyton-Jones
| The most substantial problem is that the threaded RTS in GHC 6.8.2 is | very crashy in the face of par: about 90% of my runs fail with a | segfault or an assertion failure. Simon Marlow mentioned that this bug | is fixed, but I've been unsuccessful in building a GHC 6.8.3 release |

RE: Mutually recursive modules

2008-06-06 Thread Simon Peyton-Jones
Richard I'm assuming you have ready the GHC manual? http://www.haskell.org/ghc/docs/latest/html/users_guide/separate-compilation.html#mutual-recursion Yes, mutually recursive modules are fine (in GHC anyway), and should work as advertised there. Please do produce a test case if not. Thanks

RE: desperately seeking RULES help

2008-06-09 Thread Simon Peyton-Jones
The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.) What it does is this. When you call an overloaded function f :: C a = a - a, in a function g = ...f...f...

RE: desperately seeking RULES help

2008-06-09 Thread Simon Peyton-Jones
] On Behalf Of Conal Elliott Sent: 09 June 2008 16:28 To: Simon Peyton-Jones Cc: glasgow-haskell-users@haskell.org Subject: Re: desperately seeking RULES help How does method sharing interact with the ability of the rules engine to look through lets? Wouldn't an f rule kick in when fint is seen

RE: Rebuilding ghc

2008-06-12 Thread Simon Peyton-Jones
Sorry about this -- it's my fault. I did validate a fix to the desugarer, but ndp isn't part of 'validate'. Turns out that the change to the desugarer provoked quite subtle and longstanding bug in the simplifier. To get rolling again, use -fno-ds-multi-tyvar. Or just don't compile NDP. I'll

RE: Record syntax and INLINE annotations

2008-06-13 Thread Simon Peyton-Jones
can you give an example? GHC should inline selectors, whether exported or not, whenever it'd help. They are implicitly defined as INLINE. Since this obviously isn’t working right, I'd like to see the code. Perhaps you can boil it down a little, and submit a ticket? Simon | -Original

RE: Record syntax and INLINE annotations

2008-06-13 Thread Simon Peyton-Jones
Might be, but Bryan said that his selectors weren't getting inlined at all, which is a bit different perhaps S | -Original Message- | From: Isaac Dupree [mailto:[EMAIL PROTECTED] | Sent: 13 June 2008 12:53 | To: Bryan O'Sullivan | Cc: Simon Peyton-Jones; glasgow-haskell-users

RE: Rebuilding ghc

2008-06-15 Thread Simon Peyton-Jones
| Where do I put -fno-ds-multi-tyvar so that the build system knows to use | it? I'm going to try build.mk. | | Ok that didn't work and I couldn't find anything about | -fno-ds-multi-tyvar in the documentation. Yes, in GhcLibHcOpts in build.mk is a good place. The flag isn't documented because

RE: Low-level array performance

2008-06-16 Thread Simon Peyton-Jones
Dan John Dias is indeed spending 6 months at Microsoft to work on GHC's back end. He's doing a pretty wholesale re-architecting job, so it will be a couple of months before we have the new setup glued together, but once we do I hope that we'll have a much more friendly framework in place for

RE: 6.8.3 against DoCon

2008-06-19 Thread Simon Peyton-Jones
| So, DoCon remains with ghc-6.8.2 -- untill GHC fixes the problem. | | Hm ... a small module needs 600 Mb instead of 80 Mb to compile, | and the release is considered as a progress. | All right, this may occur correct -- if the developers know what | namely must be fixed, and also know how to

RE: ANNOUNCE: GHC version 6.8.3 binary-dists

2008-06-21 Thread Simon Peyton-Jones
| maybe you can suggest a global flag setting that avoids too much | inlining during optimization. As I said to Serge, I *think* all this arises from the *unconditional* inlining of instance declarations, which isn't under flag control unfortunately. The only fix at the moment is to write

RE: Recursive functions and constant parameter closures (inlining/strictness analyzer question)

2008-06-22 Thread Simon Peyton-Jones
| However, if I had to pick something out of the air, I'd say this: always do | SAT when the argument in question is a function. Yes, that might well be a good heuristic to try, if you are interested to pursue this, Max. Making the function static means that it may be inlined, and that can

RE: possible OI extension

2008-06-27 Thread Simon Peyton-Jones
Yes, the idea of some kind of backtracking solution of class constraints (multiple instance declarations, choose the one whose context is indeed soluble) has often been suggested, and is quite attractive. But it raises a bunch of new complications. And your proposal does so even more, because

RE: Implicit Function Arguments

2008-06-30 Thread Simon Peyton-Jones
| This is the second time I have seen someone comment on implicit | parameters being planned for removal, so now you have my attention :). | I'd like to mention that a rather large project where I work (Galois, | Inc.) uses implicit parameters a lot, so removing support for them | would make

RE: Generalized phase control for GHC

2008-07-07 Thread Simon Peyton-Jones
| giving up. Admittedly I only have a superstition that this will be a | practical problem. I agree with Roman -- let's not bother with lenience until we need it | Secondly, I think it is quite | important to be able to specify dependencies for already declared phases. | That is, I (probably)

RE: Bug in type equality constraints?

2008-07-16 Thread Simon Peyton-Jones
Conal That looks like a bug, at least on the surface. You've clearly said that the instance for InnerSpace (u,v) can assume (Scalar u ~ Scalar v). Can you spare a moment submit a Trac report, with a reproducible test case (as small as possible, please!)? Manuel is actively working on

RE: GHC 6.6 GADT type unification vs GHC 6.8

2008-07-29 Thread Simon Peyton-Jones
GHC 6.6 was a bit more generous than GHC 6.8, but erroneously so. Specifically, GHC 6.8 and all subsequent versions require that when you pattern match on a value of GADT type, * the type of the scrutinee * the type of the result of the case * the types of any free

RE: GHC 6.6 GADT type unification vs GHC 6.8

2008-07-29 Thread Simon Peyton-Jones
. Dimitrios or Stephanie may have a better memory. Simon From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Jason Dagit Sent: 29 July 2008 15:14 To: Simon Peyton-Jones Cc: glasgow-haskell-users@haskell.org Subject: Re: GHC 6.6 GADT type unification vs GHC 6.8 On Tue, Jul 29, 2008 at 1:07

RE: Need help with GHC API and GHC internals

2008-08-04 Thread Simon Peyton-Jones
* Claus is right to say that you want the *renamed* tree, not the *parsed* tree. * He's also right to point to the under-development generic programming stuff for the GHC API. I'm not certain about how settled they are right now though. * But in fact you can get exactly what you want from the

Confusing flags for RULES in GHC

2008-08-11 Thread Simon Peyton-Jones
Friends The use of flags to control rewrite rules in GHC is very confusing. Several bug reports arise from this. There is a summary here: http://hackage.haskell.org/trac/ghc/ticket/2497 The final comment is a proposal, which I append below. This email is just to allow others to

RE: Version control systems

2008-08-12 Thread Simon Peyton-Jones
| It is worth pointing out that I *never* validate against ghc head when | I commit to the core libraries. I think that's perfectly reasonable for the reasons you explain. Simon ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

RE: Version control systems

2008-08-12 Thread Simon Peyton-Jones
Friends | I see more and more workarounds for workarounds for an unmaintainable | (and unusable) build system, and after the latest discussions about | git vs. darcs, maintaining GHC-specific branches of libraries etc., | I think I'll just drop maintainership from all GHC-related OpenBSD |

RE: Version control systems

2008-08-13 Thread Simon Peyton-Jones
| FWIW, I started a wiki page that tries a direct comparison between | Darcs and Git: | |http://hackage.haskell.org/trac/ghc/wiki/GitForDarcsUsers Very helpful thank you! Simon ___ Glasgow-haskell-users mailing list

RE: dataflow rewriting engine

2008-08-26 Thread Simon Peyton-Jones
Norman, John Would you care to respond to this? (Perhaps by amplifying the wiki page?) A good starting point is perhaps Craig's paper. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On | Behalf Of Chad Scherrer | Sent: 22 August 2008 22:21 | To: GHC

GHC's build system

2008-08-26 Thread Simon Peyton-Jones
Friends There's been quite a bit of discussion about GHC's build system recently, and in particular about the use of Cabal. Responding to that discussion we now have a new plan, described here: http://hackage.haskell.org/trac/ghc/wiki/Design/BuildSystem If you've taken an interest in

RE: dataflow rewriting engine

2008-08-27 Thread Simon Peyton-Jones
| I think we're all rather excited about seeing this stuff land. | What's the expected timeline, wrt. ghc 6.10's release? Good question. I've updated the overview here http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/NewCodeGen to say what we plan. Simon

RE: Build system idea

2008-08-28 Thread Simon Peyton-Jones
| So Cabal takes the view that the relationship between features and | dependencies should be declarative. ... | The other principle is that the packager, the environment is in control | over what things the package 'sees'. ... | that we can and that the approach is basically sound. The fact that

RE: Build system idea

2008-08-28 Thread Simon Peyton-Jones
| Yes this means that Cabal is less general than autoconf. It was quite a | revelation when we discovered this during the design of Cabal - originally | we were going to have everything done programmatically in the Setup.hs | file, but then we realised that having the package configuration

RE: GADT pattern match in non-rigid context

2008-09-02 Thread Simon Peyton-Jones
Wolfgang You need to say that type t, the case scrutinee, has. You can use a type signature for that. Presumably the way that a' is instantiated doesn't matter, but GHC isn't clever enough to realise that. So I just instantiated it to (). The result compiles fine. Simon {-# LANGUAGE

RE: Windows build failure

2008-09-09 Thread Simon Peyton-Jones
Thanks very much Neil; we (well Ian!) will digest your efforts. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Mitchell, Neil | Sent: 09 September 2008 14:56 | To: glasgow-haskell-users@haskell.org | Subject: RE:

RE: GADT problems

2008-09-15 Thread Simon Peyton-Jones
On Sunday 14 September 2008 20:27:52 Mariusz Przygodzki wrote: Maybe they were waiting so many years because they have never asked users about what users really need and think about it. What? It's not that we hate you (unless we do). It's just that we have nothing to offer you, and you have

RE: GADT problems

-- Thread Simon Peyton-Jones
archive.com/blank.png"; google_ad_width = 160; google_ad_height = 600; google_ad_format = "160x600_as"; google_ad_channel = "8427791634"; google_color_border = "FF"; google_color_bg = "FF"; google_color_link = "006792"; google_color_url = "006792&qu

RE: GADT problems

2008-09-15 Thread Simon Peyton-Jones
: Mitchell, Neil [mailto:[EMAIL PROTECTED] | Sent: 15 September 2008 13:56 | To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org | Subject: RE: GADT problems | | | | (case undefined of Foo GadtValue - ()) :: () -- is rigid | ... | | | | But the first compiles fine, so it seems

RE: Adding (some) libraries to a GHC tree

2008-09-17 Thread Simon Peyton-Jones
good stuff -- but with a big overlap with the Getting more packages section in http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources. Do you agree? Would it be possible to merge your new paragraphs into the existing page? If the existing page is too big and hard to navigate we

RE: Adding (some) libraries to a GHC tree

2008-09-17 Thread Simon Peyton-Jones
; glasgow-haskell-users@haskell.org; Simon Peyton-Jones | Subject: RE: Adding (some) libraries to a GHC tree | | Mitchell, Neil wrote: | Hi | | The paragraph in the new page is better than the old one, but it makes | sense to have the information in only one place. When looking

RE: Adding (some) libraries to a GHC tree

2008-09-17 Thread Simon Peyton-Jones
September 2008 15:38 | To: Jost Berthold; Simon Peyton-Jones | Cc: glasgow-haskell-users@haskell.org | Subject: RE: Adding (some) libraries to a GHC tree | | Hi Jost, | | It looks great now. | | When I saw the contributed documentation I did wonder if that was the | GHC sanctioned way of adding

Type binders in rules

2008-09-19 Thread Simon Peyton-Jones
Friends This is a message for people who use RULES, to ask your opinion. Have a look at http://hackage.haskell.org/trac/ghc/ticket/2600 and add your comments if you want. The intro to the ticket appears below, so you can get an idea of whether you are interested. Simon Roman

RE: GADTs and functional dependencies

2008-09-24 Thread Simon Peyton-Jones
Wolfgang writes | data GADT a where | | GADT :: GADT () | | class Class a b | a - b | | instance Class () () | | fun :: (Class a b) = GADT a - b | fun GADT = () You're right that this program should typecheck. In the case branch we discover (locally) that a~(), and hence by the

RE: GADTs and functional dependencies

2008-09-26 Thread Simon Peyton-Jones
| To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org | Subject: Re: GADTs and functional dependencies | | This has never worked with fundeps, because it involves a *local* type | equality (one that holds | in some places and not others) and my implementation of fundeps is | fundamentally

RE: GADTs and functional dependencies

2008-09-29 Thread Simon Peyton-Jones
| while both GHC and Hugs accept this variation: | | class FD a b | a - b | f :: (FD t1 t2, FD t1 t3) = t1 - t2 - t3 | f x y = undefined | | and infer the type of 'f' to be 'f :: (FD t1 t3) = t1 - t3 - t3'. | | So they use the FD globally (when checking use of 'f'), but not locally |

RE: gadt changes in ghc 6.10

2008-10-15 Thread Simon Peyton-Jones
| After installing ghc 6.10-rc, I have a program that | no longer compiles. I get the dreaded GADT pattern match | error, instead :) I'm sorry it's dreaded! Jason is right that the key point is this: GHC now enforces the rule that in a GADT pattern match - the type of the scrutinee

RE: Strictness in data declaration not matched in assembler?

2008-10-16 Thread Simon Peyton-Jones
| I totally agree. Getting the value of the field should just evaluate | x and then use a pointer indirection; there should be no conditional | jumps involved in getting the value. | GHC is just doing the wrong thing. You're right. As Simon says, GHC's Core language has no type distinction

RE: Strictness in data declaration not matched in assembler?

2008-10-16 Thread Simon Peyton-Jones
| BUT people who care probably UNPACK their strict fields too, which | is even better. The time you can't do that is for sum types | data T = MkT ![Int] | | You also can't do it for polymorphic components. I've used code like: | |data T a = MkT !a | |foo :: T (a,b) - a |foo

RE: gadt changes in ghc 6.10

2008-10-30 Thread Simon Peyton-Jones
| In your case the error message was: | | GADT.hs:26:56: | GADT pattern match with non-rigid result type `Maybe a' | Solution: add a type signature | In a case alternative: I1 m' - m' | In the expression: case w' S of { I1 m' - m' } | In a case alternative: Wrap w' - case

RE: cross module optimization issues

2008-11-19 Thread Simon Peyton-Jones
| I'm compiling with -O2 -Wall. After looking at the Core output, I | think I've found the key difference. A function that is bound in a | where statement is different between the monolithic and split | sources. I have no idea why, though. I'll experiment with a few | different things to see

RE: ANNOUNCE: GHC version 6.10.1 - EditLine / terminal incompatibility?

2008-11-19 Thread Simon Peyton-Jones
Would it be worth adding this hard-won lore somewhere on a Wiki where it can be found later? Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Duncan Coutts | Sent: 07 November 2008 18:09 | To: GHC-users list | Cc:

RE: ghci-haskeline (was: Re: ANNOUNCE: GHC version 6.10.1 - EditLine / terminal incompatibility?)

2008-11-21 Thread Simon Peyton-Jones
| I've actually been experimenting with something similar: | | darcs get http://code.haskell.org/~judah/ghci-haskeline/ | | Current benefits over the readline/editline versions: | - Works on Windows | | I can attest to that. Nice going Judah! | | $ cabal update | $ darcs get

RE: cross module optimization issues

2008-11-21 Thread Simon Peyton-Jones
| This project is based on Oleg's Iteratee code; I started using his | IterateeM.hs and Enumerator.hs files and added my own stuff to | Enumerator.hs (thanks Oleg, great work as always). When I started | cleaning up by moving my functions from Enumerator.hs to MyEnum.hs, my | minimal test case

RE: GADT Type Checking GHC 6.10 versus older GHC

2008-11-21 Thread Simon Peyton-Jones
You need a type signature for the case expression. As Daniel says, this is worth a read http://haskell.org/haskellwiki/Upgrading_packages%23Changes_to_GADT_matching#Changes_to_GADT_matching Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL

RE: GADT Type Checking GHC 6.10 versus older GHC

2008-11-24 Thread Simon Peyton-Jones
In my case, we had rigid type signatures all over the place. The wiki document says that the type must be rigid at the point of the match. I guess that's what we were violating. If the code I posted isn't supposed to type check then I would like to report, as user feedback, that GADTs have

RE: Linking to Haskell code from an external program

2008-11-24 Thread Simon Peyton-Jones
It looks as if you are somehow failing to link your binary with package 'base'. (Are you using 'ghc' as your linker; you should be.) But others are better than I at this kind of stuff. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL

RE: Can't compile GHC 6.8.2

2008-11-24 Thread Simon Peyton-Jones
Ah hum. We probably have not compiled GHC 6.8 with 6.2 for some time. Worse, we don't even clearly document what the oldest version is that should bootstrap any given version. Ian: could you extend the building guide http://hackage.haskell.org/trac/ghc/wiki/Building (perhaps the what tools

Fun with type functions

2008-11-27 Thread Simon Peyton-Jones
Friends GHC has embodied data type families since 6.8, and now type synonym families (aka type functions) in 6.10. However, apart from our initial papers there isn't much published material about how to *use* type families. But that hasn't stopped you: quite a few people are using them

RE: GADT Type Checking GHC 6.10 versus older GHC

2008-11-28 Thread Simon Peyton-Jones
| I also feel that the type errors given when working with existential | types, especially GADTs with existentials, are confusing. I think | | I am using existential types to test GADT code. See | http://www.haskell.org/haskellwiki/QuickCheck_/_GADT which no longer | works with 6.10.1. Really?

RE: GADT Type Checking GHC 6.10 versus older GHC

2008-11-28 Thread Simon Peyton-Jones
| arbitrarySeq :: Sequence a - Gen RepSeqVal | arbitrarySeq Nil = | return (RepSeqVal Nil Empty) | arbitrarySeq (Cons (CTMandatory (NamedType n i t)) ts) = | do u - arbitraryType t |us - arbitrarySeq ts |case u of | RepTypeVal a v - | case us of |

RE: cross module optimization issues

2008-11-28 Thread Simon Peyton-Jones
| To: Simon Peyton-Jones | Cc: Neil Mitchell; glasgow-haskell-users@haskell.org; Don Stewart | Subject: Re: cross module optimization issues | | Neil, thank you very much for taking the time to look at this; I | greatly appreciate it. | | One thing I don't understand is why the specializations

Platforms that GHC supports

2008-12-01 Thread Simon Peyton-Jones
Friends Lots of the bug reports on the GHC bug tracker are platform-specific. We thought it'd help for us to articulate more clearly what platforms GHC supports, and what we'd like it to support. Look here: http://hackage.haskell.org/trac/ghc/wiki/Platforms What you'll notice is

RE: length of module name affecting performance??

2008-12-29 Thread Simon Peyton-Jones
| Subject: Re: length of module name affecting performance?? | | That's a truly awesome feature! I'll shorten all my module names to | single letters tomorrow. Awesome indeed :-). Try shortening all your variable names to single letters to, to see if that helps. Oh, and delete all comments.

RE: black hole detection and concurrency

2008-12-29 Thread Simon Peyton-Jones
I have not followed the details of this thread, but Simon Marlow will be back in action on 5 Jan and he should know. What I do know is that this is supposed to happen: * If a *synchronous* exception S is raised when evaluating a thunk, the thunk is permanently updated to throw S. *

RE: black hole detection and concurrency

2008-12-29 Thread Simon Peyton-Jones
| I have a good theory on the latter symptom (the thread killed | message). Sticking in some traces, as in my appended code, helped me | to see what's going on. It seems to be exactly what you describe -- | the variable v is permanently bound to the exception it evaluates | to. Since the right

RE: ghc -O2 and class dictionaries

2008-12-29 Thread Simon Peyton-Jones
Which version of GHC are you using? GHC 6.10 implements automatically precisely the transformation you give below. If the difference shows up in GHC 6.10, could you spare a moment to produce a reproducible test case, and record it in GHC's bug tracker? Thanks Simon | -Original

RE: GADT Strangeness

2008-12-29 Thread Simon Peyton-Jones
| If I remove -XScopedTypeVariables from this http://hpaste.org/13230 then | I get the following error message: | | Asn1cTestNew.hs:55:27: | GADT pattern match in non-rigid context for `INTEGER' |Solution: add a type signature | In the pattern: INTEGER | In the definition

RE: GADT Strangeness

2009-01-05 Thread Simon Peyton-Jones
| Thanks very much for this. I would never have guessed to use | -XRelaxedPolyRec given the error message. | | Is it worth noting it here | http://haskell.org/haskellwiki/Upgrading_packages#Changes_to_GADT_matching | or is it something that has always existed with GADTs and I just didn't | trip

RE: Differences in pattern matching syntax?

2009-01-13 Thread Simon Peyton-Jones
I agree that's odd. Are you using -O? Can you give us a reproducible test case? (The only think I can think is that the line |Gc{} - Tm (grspe r) will build a thunk for (grspe r), and depending on the context I suppose you might get a lot of those.) Thanks Simon |

  1   2   3   4   5   6   7   8   9   10   >