RE: Advice on type families and non-injectivity?

2013-01-14 Thread Simon Peyton-Jones
| > > {-# LANGUAGE TypeFamilies #-} | > > | > > type family F a | > > | > > foo :: F a | > > foo = undefined | > > | > > bar :: F a | > > bar = foo There is a real difficulty here with type-checking 'bar'. (And that difficulty is why 'foo' is also rejected.) Namely, when typechecking 'bar', we

RE: Class instance specificity order (was Re: Fundeps and type equality)

2013-01-11 Thread Simon Peyton-Jones
| The -XOverlappingInstances flag instructs GHC to allow more than one | instance to match, provided there is a most specific one. For example, | the constraint C Int [Int] matches instances (A), (C) and (D), but the | last is more specific, and hence is chosen. If there is no most-specific |

RE: Fundeps and type equality

2013-01-11 Thread Simon Peyton-Jones
...@haskell.org; Simon Peyton-Jones; GHC Users Mailing List Subject: Re: Fundeps and type equality Yes, I finished and pushed in December. A description of the design and how to use the feature is here: http://hackage.haskell.org/trac/ghc/wiki/NewAxioms There's also a section (7.7.2.2 to be

RE: Class instance specificity order (was Re: Fundeps and type equality)

2013-01-10 Thread Simon Peyton-Jones
asgow-haskell-users@haskell.org | Cc: Richard Eisenberg; Martin Sulzmann; Simon Peyton-Jones | Subject: Class instance specificity order (was Re: Fundeps and type equality) | | On January 10, 2013 13:56:02 Richard Eisenberg wrote: | > Class instances that overlap are chosen among by order of spe

RE: DoCon and GHC

2013-01-03 Thread Simon Peyton-Jones
OK I have tested with today's GHC 7.6.2, which is very slightly later than the release candidate. When I add (EuclideanRing (UPol k)) to the signature for cubicExt, the whole of demotest compiles. So that works. Your misconception is here: | c) Pol3_ has |instance (LinSolvRing (Pol a),

RE: DoCon and GHC

2013-01-02 Thread Simon Peyton-Jones
I made a second mistake. I meant (LinSolvRing (UPol k)). Apologies. | > I don't know why 7.4 accepts it, but I'm not inclined to investigate... | > looks like a bug in 7.4. | | ghc-7.4.1 may use a special trick, but is correct. I don't understand your explanation. What is wrong with this r

RE: DoCon and GHC

2013-01-02 Thread Simon Peyton-Jones
| > The solution is to add (EuclideanRing k) to the type sig of cubicExt. | > Then it compiles all the way up to the top. | | But the DoCon declares |class (EuclideanRing a, FactorizationRing a) => Field a | | (EuclideanRing is a superclass for Field), | and the test decl

RE: Fundeps and type equality

2013-01-02 Thread Simon Peyton-Jones
As far as I understand, the reason that GHC does not construct such proofs is that it can't express them in its internal proof language (System FC). Iavor is quite right It seems to me that it should be fairly straight-forward to extend FC to support this sort of proof, but I have not been able

RE: Is there a workaround for this bug?

2013-01-01 Thread Simon Peyton-Jones
I think the patch did get into 7.6.2 (which is about to be released) though. I don't think there's a workaround, except by not using External Core, or not using Integer literals (use Ints?). Sorry. Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:

RE: Suppress "Duplicate constraints" warning?

2012-12-31 Thread Simon Peyton-Jones
Hmm. Actually there isn't a flag to suppress it, I'm afraid. Would you like me to add one? (It would be easy to do.) Simon From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Conal Elliott Sent: 30 December 2012 19:56 To: glasgow-hask

RE: Suppress "Duplicate constraints" warning?

2012-12-31 Thread Simon Peyton-Jones
| I second the question. In my case the code is neither generated nor | contains any literal duplicate constraints, but I'm still getting the | warning. If you think there's a bug (a warning for something that isn't true), by all means submit a bug report. Simon

RE: SpecConstr and GADTs

2012-12-19 Thread Simon Peyton-Jones
Some quick thoughts * SpecConstr is careful not to generate specialisations that already exist, so it should be ok to run it more than once. * SpecConstr can generate a LOT of code, so I'm looking for a way to make it a bit more selective. The "phantom-type" idea is one such.

RE: How to start with GHC development?

2012-12-19 Thread Simon Peyton-Jones
| > http://hackage.haskell.org/trac/ghc/wiki/Repositories | Very nice! WorkingConventions/Repositories still duplicates some | information The latter page should disappear; it is 100% covered by the other two. If you can find any links to it, please edit them into links to the new pages. | Re

RE: How to start with GHC development?

2012-12-19 Thread Simon Peyton-Jones
| > The first page lists the repositories and where the upstreams and | > mirrors are. The second page contains the conventions for working on | > other repositories (which is why it's under WorkingConventions). | I would find it more intuitive to have one page with couple of sections: | 1) Struc

RE: How to start with GHC development?

2012-12-18 Thread Simon Peyton-Jones
| > It seems that many informations in the wiki are duplicated. There are | > two pages about | > repositories: | > http://hackage.haskell.org/trac/ghc/wiki/Repositories | > http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions/Repositori | > es (after reading the first one source tree starte

RE: Suggested policy: use declarative names for tests instead of increasing integers

2012-12-18 Thread Simon Peyton-Jones
(This belongs on cvs-ghc, or the upcoming ghc-devs.) | I find our tests to be quite hard to navigate, as the majority have | names like tc12345.hs or some such. I suggest we instead use descriptive | names like GADT.hs or PrimOps.hs instead. What do people think? We've really moved to a naming co

RE: Need workaround for lack of fromIntegral/Int->Word rules in 7.4.2

2012-12-18 Thread Simon Peyton-Jones
| Turns out that I need a larger example to trigger the bug. I can | reliable trigger it using the unordered-containers library. I won't bore | you with the details. The workaround I need is this: | | forall x. integerToWord (smallInteger x) = int2Word# x So why not just add that rule (perha

RE: Need workaround for lack of fromIntegral/Int->Word rules in 7.4.2

2012-12-17 Thread Simon Peyton-Jones
I don't understand the problem clearly enough to help. Can you give a concrete example? Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Johan Tibell | Sent: 14 December 2012 23:17 | To: glasg

RE: How do we best make sure {Int,Word,Float,Double} to {Int,Word,Float,Double} conversions stay efficient

2012-12-17 Thread Simon Peyton-Jones
Best thing to do is to produce a concrete example, showing the code you think is sub-optimal Simon From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Sean Leather Sent: 14 December 2012 22:13 To: GHC Users List; Ian Lynagh Subject: Re

RE: How do we best make sure {Int,Word,Float,Double} to {Int,Word,Float,Double} conversions stay efficient

2012-12-17 Thread Simon Peyton-Jones
The sure-fire way is to make a loop that doesn't allocate if the rules fire; after all that's the ultimate goal. Then you can put it in tests/perf/should_run. doing -ddump-simpl and greping for stuff that should/should-not be there is another alternative we use in places. Simon | -Origin

RE: How to start with GHC development?

2012-12-14 Thread Simon Peyton-Jones
This thread has made it clear that we should do more to help people find a "way in" to GHC. Here is what I have done: * Started a GHC Reading List page, giving background reading. It's just a start; there are many gaps. I would lo

RE: Hoopl vs LLVM?

2012-12-13 Thread Simon Peyton-Jones
| > My question was more: why do we CPS transform? I guess it's because we | > manage our own stack? | | Right. In fact, LLVM does its own CPS transform (but doesn't call it | that) when the code contains non-tail function calls. We give LLVM code | with tail-calls only. | | The choice about wh

RE: Hoopl vs LLVM?

2012-12-11 Thread Simon Peyton-Jones
| In my opinion we should only implement optimizations in Hoopl that | LLVM cannot do due to lack high-level information that we might have | gotten rid of before we reach the LLVM code generator*. I don't think Indeed. And I think there is probably quite a lot that is in reach for C--, but o

RE: Which of the following PrimTyCons have a pointer-sized representations

2012-12-07 Thread Simon Peyton-Jones
You can use TyCon.tyConPrimRep, followed by primRepSizeW Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Johan Tibell | Sent: 06 December 2012 23:47 | To: glasgow-haskell-users | Subject: Which

RE: proposal: separate lists for ghc-cvs commits and ghc-dev chatter

2012-12-06 Thread Simon Peyton-Jones
My own understanding is this: A GHC *user* is someone who uses GHC, but doesn't care how it is implemented. A GHC *developer* is someone who wants to work on GHC itself in some way. The current mailing lists: * glasgow-haskell-users: for anything that a GHC *user* cares about * glasgow-haskell-b

The end of an era, and the dawn of a new one

2012-12-05 Thread Simon Peyton-Jones
hope will | ultimately be a good thing for Haskell too. | | What does this mean for GHC? Obviously I'll have much less time to work | on GHC, but I do hope to find time to fix a few bugs and keep things | working smoothly. Simon Peyton Jones will still be leading the project, | and we'll

RE: GHC Performance Tsar

2012-11-30 Thread Simon Peyton-Jones
If Bryan and Johan are the Performance Tsars the future looks bright. Or at least fast. Thank you. Simon From: Bryan O'Sullivan [mailto:b...@serpentine.com] Sent: 30 November 2012 16:53 To: Johan Tibell Cc: Simon Peyton-Jones; glasgow-haskell-users@haskell.org Subject: Re: GHC Perfor

RE: GHC Performance Tsar

2012-11-30 Thread Simon Peyton-Jones
to do, set it up, make sure it stays working, investigate regressions in performance. But it'd be silly to run nofib *manually* every time! Simon | -Original Message- | From: Tim Watson [mailto:watson.timo...@gmail.com] | Sent: 30 November 2012 15:51 | To: Simon Peyton-Jones | Cc: Si

GHC Performance Tsar

2012-11-30 Thread Simon Peyton-Jones
| > While writing a new nofib benchmark today I found myself wondering | > whether all the nofib benchmarks are run just before each release, I think we could do with a GHC Performance Tsar. Especially now that Simon has changed jobs, we need to try even harder to broaden the base of people who

RE: UHC-like JavaScript backend in GHC

2012-11-13 Thread Simon Peyton-Jones
| currently doing. Before I get started: does the GHC architecture | currently allow for adding a new calling convention which departs from | the conventional C FFIs and introduces a custom RTS? GHC certainly supports new back ends. You'd probably want to replace the entire back end, and go from

RE: Kind refinement in type families with PolyKinds

2012-10-31 Thread Simon Peyton-Jones
I think the issue is this. We have Strip :: forall k. * -> k When you say type instance Strip (Maybe a) = Maybe GHC infers the kind arguments (as with all hidden argument) to get type instance Strip (*->*) (Maybe a) = Maybe It would be fine to have another type instance like

RE: ghc: panic! (the 'impossible' happened)

2012-10-28 Thread Simon Peyton-Jones
Thanks. Certainly a bug. I've created a ticket http://hackage.haskell.org/trac/ghc/ticket/7372. Turns out that it's fixed in HEAD already, and I *think* the fix is in http://hackage.haskell.org/trac/ghc/ticket/7312, which should get into 7.6.2. Simon | -Original Message- | From: gla

RE: Proposal: EPHEMERAL pragma

2012-10-25 Thread Simon Peyton-Jones
9:56 AM, José Pedro Magalhães mailto:j...@cs.uu.nl>> wrote: Hi all, Following up on a chat with Simon Peyton Jones at ICFP, I would like to discuss the possible introduction of a EPHEMERAL pragma. For example: {-# EPHEMERAL Rep #-} data Rep = ... This pragma would indicate that the program

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-10-15 Thread Simon Peyton-Jones
ure how, it at all, it affects Richard's singletons paper Simon From: Iavor Diatchki [mailto:diatc...@galois.com] Sent: 12 October 2012 21:11 To: Richard Eisenberg Cc: Nicolas Frisby; Simon Peyton-Jones; Stephanie Weirich; Conor McBride; glasgow-haskell-users@haskell.org Subject: Re: Pol

RE: Constructing TH types

2012-10-15 Thread Simon Peyton-Jones
Eric, Nicolas Sorry to be slow on this thread. Here's a summary. Would one of you feel able to take this summary, edit in a few examples, and add it to the (user-land) Haskell Wiki at haskell.org? There are quite a few explanatory pages about GHC there, and this explanation will otherwise ge

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-10-12 Thread Simon Peyton-Jones
| > (Also - what's the general status on this initiative? Has much | > happened in about a month?) | | From my end, nothing. I'm trying to wrap up some other work I'm doing | on GHC (ordered overlapping type family instances), and it looks like | some of the questions I raised in my last email in

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-10-12 Thread Simon Peyton-Jones
| Iavor and I collaborated on the design of the building blocks of | singleton types, as we wanted our work to be interoperable. A recent | scan through TypeLits tells me, though, that somewhere along the way, | our designs diverged a bit. Somewhere on the to-do list is to re-unify | the interfaces

RE: TypeHoles: unbound variables as named holes

2012-10-05 Thread Simon Peyton-Jones
I also like the proposal; however, I think it only makes sense if the set of unbound variables with the same name is treated as referring to the same identifier. This was, after all, the main reason for named holes. Roman expected this, and I think everybody who uses the feature will expect it.

RE: Comments on current TypeHoles implementation

2012-10-05 Thread Simon Peyton-Jones
| Sounds cool. I would also expect that if you have several occurences of | the same unbound identifier, then it gets a unified type. I thought about this, but I think not. Consider f x1 = _y g x2 = _y Do you want _y and _y to be unified, so that f and g are no longer polymorphic? I think not.

RE: Comments on current TypeHoles implementation

2012-10-04 Thread Simon Peyton-Jones
uage pragma while -fdefer-type-errors is a compiler flag. Maybe we should have -XDeferTypeErrors?) Simon From: sean.leat...@gmail.com [mailto:sean.leat...@gmail.com] On Behalf Of Sean Leather Sent: 03 October 2012 16:45 To: Simon Peyton-Jones Cc: GHC Users List; Thijs Alkemade Subject: Comments

RE: Comments on current TypeHoles implementation

2012-10-04 Thread Simon Peyton-Jones
Thanks for all your work in getting TypeHoles into HEAD. We really appreciate it. Great - maybe you can develop it further. (2) There is a strange case where an error is not reported for a missing type class instance, even though there is no (apparent) relation between the missing instance an

RE: Simplification of instances

2012-09-28 Thread Simon Peyton-Jones
Ahem. DFuns (what you get from is_dfun of a ClsInst) now have some "silent" arguments, that are added by GHC and are not part of the original instance declaration. See Note [Silent superclass arguments] in TcInstDcls. But you don't want to print them. Just do what InstEnv.pprInstanceHdr does (

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-09-18 Thread Simon Peyton-Jones
that's a bit complicated notationally. http://hackage.haskell.org/trac/ghc/wiki/ExplicitTypeApplication Does anyone have any other ideas? Simon | -----Original Message- | From: Simon Peyton-Jones | Sent: 16 September 2012 16:49 | To: Richard Eisenberg; Andrea Vezzosi | Cc: Adam Gundry; Conor

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-09-18 Thread Simon Peyton-Jones
| Will unsafeCoercing to and from Any still work with this plan? (If not | then I can just use data Anything = forall a. Anything a, so it's not a | big deal.) Yes I think it'll be fine, but thanks for highlighting this other use of Any. Simon ___ Gla

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-09-16 Thread Simon Peyton-Jones
Friends Thanks for this useful conversation, by email and at ICFP. Here's my summary. Please tell me if I'm on the right track. It would be great if someone wanted to create a page on the GHC wiki to capture the issues and outcomes. Simon Eta rules ~~ * We want to add eta-rules to FC.

RE: Type operators in GHC

2012-09-14 Thread Simon Peyton-Jones
iable operator Any other opinions? Simon From: conal.elli...@gmail.com [mailto:conal.elli...@gmail.com] On Behalf Of Conal Elliott Sent: 06 September 2012 23:59 To: Simon Peyton-Jones Cc: GHC users Subject: Re: Type operators in GHC Oh dear. I'm very sorry to have missed this discussi

RE: Constraint error related to type family and higher-rank type

2012-09-03 Thread Simon Peyton-Jones
This is delicate. First, make sure you read the paper "Modular type inference with local assumptions" (on my home page). Now, typechecking v's RHS will generate this implication constraint (see the paper): (forall b. (C alpha b, TF b ~ Y) => C A beta, TF beta ~ Y, b~beta) where 'alpha' is

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Simon Peyton-Jones
come after that. If it can’t be expressed in FC it’s out of court. Of course we can always beef up System FC. I’m copying Stephanie and Conor who may have light to shed. Simon From: Edward Kmett [mailto:ekm...@gmail.com] Sent: 31 August 2012 18:27 To: Simon Peyton-Jones Cc: glasgow-haskel

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Simon Peyton-Jones
From: Edward Kmett [mailto:ekm...@gmail.com] Sent: 31 August 2012 13:45 To: Simon Peyton-Jones Cc: glasgow-haskell-users@haskell.org Subject: Re: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency? Hrmm. This seems to render product kinds rather useless, as there is no way

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Simon Peyton-Jones
Hrmm. This seems to render product kinds rather useless, as there is no way to refine the code to reflect the knowledge that they are inhabited by a single constructor. =( Wait. When you say “This seems to render produce kinds useless”, are you saying that in the code I wrote, you think irt sho

RE: PolyKind issue in GHC 7.6.1rc1: How to make a kind a functional dependency?

2012-08-31 Thread Simon Peyton-Jones
With the code below, I get this error message with HEAD. And that looks right to me, no? The current 7.6 branch gives the same message printed less prettily. If I replace the defn of irt with irt :: a '(i,j) -> Thrist a '(i,j) irt ax = ax :- Nil then it typechecks. Simon Knett.hs:20:10: C

RE: 7.6.1 RC1 panic "coVarsOfTcCo:Bind"

2012-08-22 Thread Simon Peyton-Jones
Ah. Hmm. I see. Can you try this in TcEvidence -- We expect only coercion bindings go_bind :: EvBind -> VarSet go_bind (EvBind _ (EvCoercion co)) = go co go_bind (EvBind _ (EvId v))= unitVarSet v go_bind other = pprPanic "coVarsOfTcCo:Bind" (ppr other) with this ins

RE: Holes in GHC

2012-08-21 Thread Simon Peyton-Jones
Can you give me read/write access to your github repo? I'm simonpj on github. That way I can add comments/questions in code, and generally clean up. It would make things easier if you could merge with HEAD so that I don't have to mess around moving libraries back in time. -

RE: build failures when hiding non-visible imports

2012-08-21 Thread Simon Peyton-Jones
OK we're doing this for 7.6. See http://hackage.haskell.org/trac/ghc/ticket/7167 | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow- | haskell-users-boun...@haskell.org] On Behalf Of Conrad Parker | Sent: 21 August 2012 01:02 | To: John Lato | Cc: glas

RE: funny type inference error with ghc7.6rc1

2012-08-20 Thread Simon Peyton-Jones
That does seem odd. Can you give instructions for how to reproduce this? The fewer dependencies the better :-) Simon From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Carter Schonwald Sent: 17 August 2012 19:01 To: GHC Users List S

RE: build failures when hiding non-visible imports

2012-08-17 Thread Simon Peyton-Jones
| Would it be reasonable to change ghc's behavior to treat this | (ie an 'import' statement that hides something that isn't exported) as a | warning instead of an error? Yes, that would be easy if it's what everyone wants. Any other opinions? Simon | -Original Message- | From: glasgow-

RE: Non-updateable thunks

2012-08-14 Thread Simon Peyton-Jones
The update analysis developed by Keith Wansbrough was very complicated, and although rather beautiful (read his thesis and our papers), it didn't pay its way in terms of complexity. Coincidentally, Ilya Sergey is here on an internship and is now working on a "cheap and cheerful" update analysis

GADTs in the wild

2012-08-14 Thread Simon Peyton-Jones
Friends I'm giving a series of five lectures at the Laser Summer School (2-8 Sept), on "Adventures with types in Haskell". My plan is: 1. Type classes 2. Type families [examples including Repa type tags] 3. GADTs 4. Kind polymorphism 5. System FC a

RE: PolyKinds, Control.Category and GHC 7.6.1

2012-08-14 Thread Simon Peyton-Jones
| FWIW PolyKinds in 7.4 is rough, and I had experiences where enabling it | led to compile failures in downstream modules, so this wouldn't | necessarily have been painless. Hopefully with 7.6 it will be. PolyKinds is not an advertised feature of 7.4, so you should absolutely not rely on it worki

RE: “Ambiguous type variable in the constraint” error in rewrite rule

2012-07-16 Thread Simon Peyton-Jones
| > Ah! This rule will only match if the LHS is | > | > f (WriterT w Identity) ($fMonadWriterT w Identity dm | > $fMonadIdentity) | > | > So it's a nested pattern match. That makes the LHS match less often; | namely only when the dictionary argument to 'f' is an application of | $fMonadWr

RE: “Ambiguous type variable in the constraint” error in rewrite rule

2012-07-12 Thread Simon Peyton-Jones
The error message is unhelpful. HEAD reports this: Could not deduce (Monoid w) arising from a use of `g' from the context (Monad (WriterT w Identity)) bound by the RULE "f->g" at Foo.hs:14:3-14 Possible fix: add (Monoid w) to the context of the RULE "f->g" In the expression:

RE: Call to arms: lambda-case is stuck and needs your help

2012-07-09 Thread Simon Peyton-Jones
| I strongly favor a solution where lambda-case expressions start with \, | because this can be generalized to proc expressions from arrow syntax | simply by replacing the \ with proc. | | Take, for example, the following function definition: | | f (Left x) = g x | f (Right y) = h y | |

RE: More infinite simplifier bugs?

2012-07-06 Thread Simon Peyton-Jones
try with -ddump-rule-firings -dverbose-core2core -ddump-occur-anal -ddump-inlinings. You'll get a lot of output ,but you may either see (a) output stops but computer gets hot, (b) output goes on and on. use HEAD if you can Simon | -Original Message- | From: glasgow-haskell-users-b

RE: API function to check whether one type fits "in" another

2012-06-29 Thread Simon Peyton-Jones
holes" that Thijs is working on might be good for you. He has a prototype already I think. Simon | -Original Message- | From: "Philip K. F. Hölzenspies" [mailto:p...@st-andrews.ac.uk] | Sent: 28 June 2012 11:11 | To: Simon Peyton-Jones | Cc: thijsalkem...@gmail.com

RE: Fwd: ghc-7.6 branch

2012-06-28 Thread Simon Peyton-Jones
| > Has maintainer's not being responsive been a problem for GHC in the | > past? | | Yes. Some of the upstreams respond so fast that it makes my head spin, | while others often either don't respond or continually promise to get to | things soon. (again, these are good, well-meaning people,

RE: Strange behavior when using stable names inside ghci?

2012-06-28 Thread Simon Peyton-Jones
You are, in effect, doing pointer equality here, which is certain to be fragile, ESPECIALLY if you are not optimising the code (as is the case in GHCi). I'd be inclined to seek a more robust way to solve whatever problem you started with Simon | -Original Message- | From: glasgow-ha

RE: API function to check whether one type fits "in" another

2012-06-28 Thread Simon Peyton-Jones
Philip | What I'm looking for is a function | | fitsInto :: TermType -> HoleType -> Maybe [(TyVar,Type)] Happily there is such a function, but you will need to become quite familiar with GHC's type inference engine. We need to tighten up the specification first. I believe that you have fu

RE: Kindness of strangers (or strangeness of Kinds)

2012-06-08 Thread Simon Peyton-Jones
There is a little, ill-documented, sub-kind hierarchy in GHC. I'm trying hard to get rid of it as much as possible, and it is much less important than it used to be. It's always been there, and is nothing to do with polykinds. I've extended the commentary a bit: see "Types" and "Kinds" here htt

RE: Known problems with promoted tuples and lists in GHC 7.4.1?

2012-06-06 Thread Simon Peyton-Jones
Kind polymorphism and promoted kinds is *not* an advertised feature of 7.4.1. Much code is there, but it doesn't work when you push it. The HEAD does work. If you are using kind polymorphism or promoted kinds, use HEAD (or a development snapshot). Indeed not_okay compiles fine with HEAD Sim

RE: Source Location of DataCon objects in GHC 7.4.1 API

2012-06-05 Thread Simon Peyton-Jones
5, 2012 at 2:49 PM, Simon Peyton-Jones | wrote: | > That's our policy too, as you will see if you look at any closed Trac | ticket.  We have thousands of regression tests, and they are fabulously | useful.  But it's a judgement call when the scope is extremely narrow | and the regressi

RE: Source Location of DataCon objects in GHC 7.4.1 API

2012-06-05 Thread Simon Peyton-Jones
all means submit a regression test for this one; I'll gladly commit it. S | -Original Message- | From: Jacques Carette [mailto:care...@mcmaster.ca] | Sent: 05 June 2012 13:45 | To: Simon Peyton-Jones | Cc: JP Moresmau; glasgow-haskell-users@haskell.org | Subject: Re: Source Location of

RE: Source Location of DataCon objects in GHC 7.4.1 API

2012-06-05 Thread Simon Peyton-Jones
Done. I don't think it's worth a regression test. SImon commit cb705a38d677e2ab4cad37447c8180bd397d5576 Author: Simon Peyton Jones Date: Tue Jun 5 13:35:07 2012 +0100 Add sensible locations to record-selector bindings compiler/typecheck/TcTyClsDecls.

RE: Source Location of DataCon objects in GHC 7.4.1 API

2012-06-05 Thread Simon Peyton-Jones
Ah I see. I'm fixing this. Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of JP Moresmau | Sent: 01 June 2012 10:25 | To: glasgow-haskell-users@haskell.org | Subject: Source Location of DataCon

RE: Prelude for type-level programming

2012-04-25 Thread Simon Peyton-Jones
Thanks Etienne When I tried to compile your Type.hs file, the first thing that broke was this: class ((ma :: m a) >>= (f :: a -> m b -> Constraint)) (mb :: m b) | ma f -> mb You want the sort of 'm' to be BOX -> BOX, but you can't do this at the moment. As our paper say, the sort system is pret

RE: default instance for IsString

2012-04-24 Thread Simon Peyton-Jones
I'm not following the details of this thread, but if you guys can come to a conclusion and write up a design, I'd be happy to discuss it. If you want validation of literal strings, then TH quasiquotes are the way to go: [url| http://this/that |] will let you specify the parser/validato

RE: default instance for IsString

2012-04-22 Thread Simon Peyton-Jones
| Couldn't we make a special case for IsString, like we do for Num, | given it's special syntactic association with OverloadedStrings? Maybe so. It's open to anyone to make a concrete proposal. See http://hackage.haskell.org/trac/ghc/ticket/6030 which may be the same issue. Simon | -Or

RE: ANNOUNCE: GHC version 7.2.1 - {-# LANGUAGE NoTraditionalRecordSyntax #-}

2012-03-27 Thread Simon Peyton-Jones
ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions for me. The flag appears to just disable record construction and update syntax, and record patterns, and record syntax in GADT declarations. It has probably never been used. Simon | -Original Message- | Fro

RE: Stealing ideas from the latest GCC release

2012-03-23 Thread Simon Peyton-Jones
Good for JHC! Indeed; see http://hackage.haskell.org/trac/ghc/ticket/5059 There are two big questions: * When to specialise (a supercompiler specialises on everything) * How to make sure that the arguments are not inlined too early (see the ticket) Simon | -Original Message- | From: gla

RE: profiling and backtracing blues

2012-03-16 Thread Simon Peyton-Jones
Yes, that'll be it. You probably don't care about the annotations when doing it for this purpose? We can probably have a flag to make it ignore annotations; or always do so if the interpreter is not on. That way you would not have to comment it out. S | -Original Message- | From:

RE: packaged up polykinded types can't index type families?

2012-03-13 Thread Simon Peyton-Jones
I'm afraid that PolyKinds is not an advertised feature of 7.4.1, and we won't fix bugs in it. The flag exists because we were working on it before releasing 7.4, but it was too far from completion to support. We knew there were many bugs, but did not want to hold up 7.4 for them. (Otherwise w

RE: Interpreting the strictness annotations output by ghc --show-iface

2012-03-08 Thread Simon Peyton-Jones
| I'm not sure but the trailing "m" in g's signature. That says that the result has the CPR property. S ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

RE: Interpreting the strictness annotations output by ghc --show-iface

2012-03-08 Thread Simon Peyton-Jones
The "C" is a call demand: C(d) means "this function is called and its result is consumed with d. U(ddd) means "this three-field product is evaluated, and its three field are evaluated with d,d,d | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haske

RE: Abstracting over things that can be unpacked

2012-03-06 Thread Simon Peyton-Jones
First idea: instead of rejecting unpack pragmas on polymorphic fields, have them require a class constraint on the field types. Example: data UnboxPair a b = (Unbox a, Unbox b) => UP {-# UNPACK #-} !a {-# UNPACK #-} !b The Unbox type class would be similar in spirit to the class with the s

RE: Unpack primitive types by default in data

2012-02-17 Thread Simon Peyton-Jones
You do know about -funbox-strict-fields, a flag that exists already, don't you. (Sorry if I'm behind the curve here; have not followed the thread.) S | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of

RE: Changes to Typeable

2012-02-13 Thread Simon Peyton-Jones
| Should there perhaps be a NewTypeable module which could then be renamed | into Typeable once it is sufficiently well established? I started with that idea, but there would be a 2-stage process: * Step 1: (when PolyTypable becomes available) People change to import Data.PolyTypeable * Step

RE: Changes to Typeable

2012-02-10 Thread Simon Peyton-Jones
| Where is Proxy data type defined? In the section "The new Typeable class" of http://hackage.haskell.org/trac/ghc/wiki/GhcKinds/PolyTypeable | Which instances should it have? Well, Typeable, perhaps! But that is no so relevant here. S ___ Glasg

Changes to Typeable

2012-02-10 Thread Simon Peyton-Jones
Friends The page describes an improved implementation of the Typeable class, making use of polymorphic kinds. Technically it is straightforward, but it represents a non-backward-compatible change to a widely used library, so we need to make a plan for the transition. http://hackage.ha

RE: auto-orphans?

2012-02-10 Thread Simon Peyton-Jones
Fixed, thank you. Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Christian Maeder | Sent: 07 February 2012 11:33 | To: GHC Users Mailing List | Subject: auto-orphans? | | Hi, | | in | http:/

RE: Records in Haskell

2012-02-10 Thread Simon Peyton-Jones
| The starting point a new records implementation was to be pragmatic | and get something done. Simon has identified that Has constraints are | required to implement records. I think it'd be overstating it to say "required". But Has constraints do seem to be a modest way to make progress that fi

RE: Kind error in GHC-7.4.1, works in GHC-7.2.2

2012-02-10 Thread Simon Peyton-Jones
It should not have worked before. Consider I# $ 3# ($) is a polymorphic function and takes two *pointer* arguments. If we actually called it with I# and 3# as arguments we might seg-fault when we call the GC when allocating the box. Polymorphic type variables (in this case in th

RE: ANNOUNCE: GHC version 7.4.1

2012-02-03 Thread Simon Peyton-Jones
|= | The (Interactive) Glasgow Haskell Compiler -- version 7.4.1 |= ... | * There is a new feature kind polymorphism (-XPolyKinds). | A side-effect of this is th

RE: ANNOUNCE: GHC 7.4.1 Release Candidate 2

2012-02-01 Thread Simon Peyton-Jones
Trac #5623 is very much on my radar; it's just that I have been too snowed under to get to it. It's not entirely straightforward because the inlining machinery needs careful modification, lest one fix one performance bug only to introduce another. So the bug is still in 7.4 I'm afraid. I will

RE: Impredicative types error

2012-02-01 Thread Simon Peyton-Jones
John Impredicative polymorphism has always been a soggy area of GHC -- the mixture of type inference and impredicativity is a genuinely difficult problem as you'll see from reading the papers. GHC 7 is less ambitious than GHC 6, and does a bit less. Tim Sheard, Dimitrios Vytiniotis and I ar

RE: ANNOUNCE: GHC 7.4.1 Release Candidate 2

2012-02-01 Thread Simon Peyton-Jones
Austin The ticket (#5719) says "merge if you like but I don't think it's needed". No one complained at the time, so Ian didn't merge it. He's tried merging just the patches you identify, but they don't merge cleanly any more. So I'm afraid this particular fix won't be in 7.4. Sorry. Simon

RE: [Haskell-cafe] Some thoughts on Type-Directed Name

2012-01-30 Thread Simon Peyton-Jones
| What would really, really help me is for someone to have a look at the 'solution' I | posted to the difficulties SPJ saw with the SORF approach. (I ref'd it in my reply to In response to your plea, I took a look at your post http://www.haskell.org/pipermail/glasgow-haskell-users/2011-Dece

RE: Holes in GHC

2012-01-26 Thread Simon Peyton-Jones
| The primary goal is to make this part of GHCi. Say, you're working on | a file Foo.hs in your favorite editor, and you have: Aha. That is helpful (below). Start a GHC wiki page to describe? Now, if I compile {-# LANGUAGE ImplicitParams #-} module Foo where foo

RE: Holes in GHC

2012-01-26 Thread Simon Peyton-Jones
| > Let me try to describe the goal better. The intended users are people | > new to Haskell or people working with existing code they are not | > familiar with. | | Also me. I want this feature. My question remains: what is the feature? Agda has a sophisticated IDE; is that a key part o

RE: Holes in GHC

2012-01-26 Thread Simon Peyton-Jones
| This is where you would want to use a hole. Just like undefined, it | has type `a`, so it can be used anywhere (and when compiling, we | intend to turn it into an exception too), but the difference with | undefined is that after the typechecking has succeeded, you get a list | of your holes,

RE: Holes in GHC

2012-01-26 Thread Simon Peyton-Jones
y the info that (I think) you want, and moreover you can do that without changing the type inference engine at all. Simon | -Original Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Simon Peyton-Jone

RE: Holes in GHC

2012-01-26 Thread Simon Peyton-Jones
Thijs You are describing the implementation of something, but you do not give a specification. It's hard for me to help you with the design of something when I don't know what the goal is. Can you give a series of concrete examples of what you want to happen? Is this just in GHCi? Or do you

<    1   2   3   4   5   6   7   8   9   10   >