RE: Pattern synonym constraints :: Ord a => () => ...

2021-10-06 Thread Simon Peyton Jones via Glasgow-haskell-users
ytonjo...@gmail.com<mailto:simon.peytonjo...@gmail.com> instead. (For now, it just forwards to simo...@microsoft.com.) From: Anthony Clayden Sent: 06 October 2021 11:42 To: Simon Peyton Jones Cc: Gergő Érdi ; GHC users Subject: Re: Pattern synonym constraints :: Ord a => () => ...

RE: Pattern synonym constraints :: Ord a => () => ...

2021-10-06 Thread Simon Peyton Jones via Glasgow-haskell-users
Perhaps I'm just stupid, and should be disqualified from using such features. Only as a result of this thread (not from the User Guide nor from the paper) do I discover "use" means match-on. You are not stupid. And since you misunderstood despite effort, the presentation is - by definition -

RE: -dinline-check for symbolic names?

2021-08-19 Thread Simon Peyton Jones via Glasgow-haskell-users
: Michael Sperber | Sent: 18 August 2021 14:14 | To: Simon Peyton Jones | Cc: glasgow-haskell-users@haskell.org | Subject: Re: -dinline-check for symbolic names? | | | On Tue, Aug 10 2021, Simon Peyton Jones wrote: | | > It's hard to tell what is happening without a repro case. Can

RE: Avoiding construction of dead dictionaries

2021-08-12 Thread Simon Peyton Jones via Glasgow-haskell-users
? Not sure what you mean here, but once we have a repro case we can discuss. Worth opening a ticket too -- email is easily lost. Thanks Simon | -Original Message- | From: Michael Sperber | Sent: 12 August 2021 10:15 | To: Simon Peyton Jones | Cc: Sebastian Graf ; glasgow-haske

RE: InstanceSigs -- rationale for the "must be more polymorphic than"

2021-08-10 Thread Simon Peyton Jones via Glasgow-haskell-users
August 2021 12:01 To: Simon Peyton Jones Cc: Anthony Clayden ; GHC users Subject: Re: InstanceSigs -- rationale for the "must be more polymorphic than" Simon, there are times when a function has to be generalized to be made polymorphic recursive. Perhaps the method takes an argument

RE: -dinline-check for symbolic names?

2021-08-10 Thread Simon Peyton Jones via Glasgow-haskell-users
It's hard to tell what is happening without a repro case. Can you share one? You suggested that it might have something to do with using an operator. Does the same thing happen if you replace the operator with an alpha-numeric name? Simon | -Original Message- | From:

RE: InstanceSigs -- rationale for the "must be more polymorphic than"

2021-08-10 Thread Simon Peyton Jones via Glasgow-haskell-users
AntC, I think you see why the instance sig must be at least as polymorphic than the instantiated signature from the class - because that's what the client is going to expect. We are building a record of functions, and they must conform to the class signature. I agree with David's (1) and (2)

RE: Avoiding construction of dead dictionaries

2021-08-09 Thread Simon Peyton Jones via Glasgow-haskell-users
Hi Mike | The right-hand argument of <+ leads to a dictionary construction that is a | proof of a certain property, but the dictionary itself ends up being dead, | like so: | |case $w$dOpCon_r2kGJ ... |of |{ (# ww1_s27L3 #) -> ... } | ^ |

RE: Avoiding construction of dead dictionaries

2021-08-09 Thread Simon Peyton Jones via Glasgow-haskell-users
> . So apparently it is possible for a dictionary to be bottom somehow. That should not happen. Except in the case of single-method dictionaries like class C a where op :: a -> a In these cases the "dictionary" is represented by a newtype, like this newtype C a =

RE: exhausted simplifier ticks and hs-boot files

2019-08-30 Thread Simon Peyton Jones via Glasgow-haskell-users
Ganesh It's an old bug that has somehow reappeared. I opened https://gitlab.haskell.org/ghc/ghc/issues/17140 But it seems OK in HEAD, and hence probably in GHC 8.8. Can you try? Maybe put further comments on the issue tracker, rather than here. thanks Simon | -Original Message- |

RE: Equality constraints (~): type-theory behind them

2019-03-25 Thread Simon Peyton Jones via Glasgow-haskell-users
I'd far rather see GHC's implementation of FunDeps made more coherent (and learning from Hugs) than squeezing it into the straitjacket of System FC and thereby lose expressivity. To call System FC a straitjacket is to suggest that there is a straightforward alternative that would serve the

Guidelines for respectful communication

2018-12-06 Thread Simon Peyton Jones via Glasgow-haskell-users
Friends As many of you will know, I have been concerned for several years about the standards of discourse in the Haskell community. I think things have improved since the period that drove me to write my Respect email,

Summit on Advances in Programming Languages 2019

2018-11-26 Thread Simon Peyton Jones via Glasgow-haskell-users
Haskellers The Summit oN Advances in Programming Languages (SNAPL) is a biennial venue for discussions about programming languages. SNAPL focuses on experience-based insight, innovation, and visionary ideas spanning from foundations to applications of

RE: Natural number comparisons with evidence

2018-05-24 Thread Simon Peyton Jones via Glasgow-haskell-users
I see this in GHC.TypeNats sameNat :: (KnownNat a, KnownNat b) => Proxy a -> Proxy b -> Maybe (a :~: b) sameNat x y | natVal x == natVal y = Just (unsafeCoerce Refl) | otherwise= Nothing The unsafeCoerce says that sameNat is part of the trusted code base. And

RE: Open up the issues tracker on ghc-proposals

2018-05-03 Thread Simon Peyton Jones via Glasgow-haskell-users
I can volunteer to at least scrape together all the objections to ScopedTypeVariables as currently. It's not yet a proposal, so not on github. Start a wiki page? A cafe thread? (It'll get lost.) A ghc-users thread? (It'll get ignored.) That’s a fair question. We have lots of forums, but your

RE: Open up the issues tracker on ghc-proposals

2018-05-02 Thread Simon Peyton Jones via Glasgow-haskell-users
| > Sometimes, a language extension idea could benefit from | some community discussion before it's ready for a formal proposal. | | Can I point out it's not only ghc developers who make proposals. I'd | rather you post this idea more widely. The Right Thing is surely for the main GHC

RE: How to highlighting subexpressions in dumped core?

2018-03-07 Thread Simon Peyton Jones via Glasgow-haskell-users
I'm not keen on adding more Tick complexity -- it's a bit out of hand already, and all transformations must "do the right thing". AnnExpr adds an annotation at every node. You could, I guess use that to annotate -- but then you'd need a pretty printer for it so you'd end up with duplication.

RE: Why is EvTerm limited?

2018-01-19 Thread Simon Peyton Jones via Glasgow-haskell-users
| What would break if we had | | | EvExpr CoreExpr | | as an additional constructor there? This has come up before. I think that'd be a solid win. In fact, eliminate all the existing evidence constructors with "smart constructors" that produce an EvExpr. That'd mean moving stuff from

RE: GHC rewrite rule type-checking failure

2017-10-03 Thread Simon Peyton Jones via Glasgow-haskell-users
* Is it feasible for GHC to combine the constraints needed LHS and RHS to form an applicability condition? I don’t think so. Remember that a rewrite rule literally rewrites LHS to RHS. It does not conjure up any new dictionaries out of thin air. In your example, (D k b) is needed in the

RE: Inhibiting the specialiser?

2017-09-15 Thread Simon Peyton Jones via Glasgow-haskell-users
Did you try -fno-specialise? From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Conal Elliott Sent: 15 September 2017 02:45 To: glasgow-haskell-users@haskell.org Subject: Inhibiting the specialiser? Is there a GHC flag for inhibiting the specializer (but

RE: Trouble with injective type families

2017-07-05 Thread Simon Peyton Jones via Glasgow-haskell-users
Functional dependencies and type-family dependencies only induce extra "improvement" constraints, not evidence. For example class C a b | a -> b where foo :: a -> b instance C Bool Int where ... f :: C Bool b => b -> Int f x = x -- Rejected Does the fundep on

RE: 8.2.1-rc2 upgrade report

2017-06-06 Thread Simon Peyton Jones via Glasgow-haskell-users
Thanks for the report. Going from 67G to 56G allocation is a very worthwhile improvement in runtime! Hurrah. However, trebling compile time is very bad. It is (I think) far from typical: generally 8.2 is faster at compiling than 8.0 so you must be hitting something weird. Anything you can

RE: Unused import warning on re-export

2017-05-11 Thread Simon Peyton Jones via Glasgow-haskell-users
| Is there a reason GHC considers this case an unused import? It seems that | the use of the import is explicitly stated right within the import | itself. Should I submit a ticket for this? Hmm. I think you are saying that module A where import B as A(f) g = True that is equivalent

RE: join points and stream fusion?

2017-04-28 Thread Simon Peyton Jones via Glasgow-haskell-users
Thank you! | -Original Message- | From: Christian Höner zu Siederdissen [mailto:choe...@bioinf.uni- | leipzig.de] | Sent: 28 April 2017 00:14 | To: Simon Peyton Jones <simo...@microsoft.com> | Cc: glasgow-haskell-users@haskell.org | Subject: Re: join points and stream

RE: join points and stream fusion?

2017-04-27 Thread Simon Peyton Jones via Glasgow-haskell-users
I'm afraid I don't have enough context to understand this thread. Could you offer a concrete example (as small as possible), and explain how to reproduce the problem you are seeing. Don't forget to give the compiler version you are using, and any libraries you depend on (as few as poss). Is

RE: Why isn't this Overlapping?

2017-04-18 Thread Simon Peyton Jones via Glasgow-haskell-users
Moreover, as discussed in the user manual section, GHC doesn’t complain about overlapping instances at the instance decl, but rather where the instances are used. That’s why there is no overlap

RE: Accessing the "original" names via GHC API

2017-01-25 Thread Simon Peyton Jones via Glasgow-haskell-users
The TyCon has a Name (use tyConName to get it). The Name has a Module and an OccName (use nameModule and nameOccName to get them) The OccName has a string (occNameString) The Module has a ModuleName and a Package. All of these will give the “original-name” info, ignoring what’s in scope. Does

RE: GHC rewrite rules for class operations & laws

2017-01-04 Thread Simon Peyton Jones via Glasgow-haskell-users
[mailto:b...@smart-cactus.org] | Sent: 29 December 2016 14:50 | To: Conal Elliott <co...@conal.net>; George Colpitts | <george.colpi...@gmail.com> | Cc: glasgow-haskell-users@haskell.org; Simon Peyton Jones | <simo...@microsoft.com> | Subject: Re: GHC rewrite rules for class

RE: GHC rewrite rules for class operations & laws

2016-11-22 Thread Simon Peyton Jones via Glasgow-haskell-users
Conal Is it possible to apply GHC rewrite rules to class methods? Not currently. See https://ghc.haskell.org/trac/ghc/ticket/11688, esp comment:7 which gives links to similar examples. https://ghc.haskell.org/trac/ghc/ticket/10528 comment:13 gives more background. It’d be great if someone

RE: Getting rid of -XImpredicativeTypes

2016-09-26 Thread Simon Peyton Jones via Glasgow-haskell-users
a swamp. I have tried multiple times to fix ImpredicativeTypes, and failed every time. Which is not to say that someone shouldn’t try again, with new thinking. Simon From: Dan Doel [mailto:dan.d...@gmail.com] Sent: 26 September 2016 00:54 To: Simon Peyton Jones <simo...@microsoft.com> Cc:

FW: Getting rid of -XImpredicativeTypes

2016-09-26 Thread Simon Peyton Jones via Glasgow-haskell-users
Friends GHC has a flag -XImpredicativeTypes that makes a half-hearted attempt to support impredicative polymorphism. But it is vestigial…. if it works, it’s really a fluke. We don’t really have a systematic story here at all. I propose, therefore, to remove it entirely. That is, if you use

RE: Type families in kind signatures with TypeInType

2016-09-23 Thread Simon Peyton Jones via Glasgow-haskell-users
19:51 To: Simon Peyton Jones <simo...@microsoft.com> Cc: glasgow-haskell-users@haskell.org Mailing List <Glasgow-haskell-users@haskell.org> Subject: Re: Type families in kind signatures with TypeInType On Fri, Sep 23, 2016 at 3:19 AM, Simon Peyton Jones <simo...@microsoft.com<mail

RE: Type families in kind signatures with TypeInType

2016-09-23 Thread Simon Peyton Jones via Glasgow-haskell-users
This is an example of https://ghc.haskell.org/trac/ghc/ticket/12088. The “type instance T List” declaration actually depends on the “type instance K List” declaration; the latter must be typechecked before the former. But this dependency is absolutely unclear. There’s a long discussion on the

RE: GHC Performance / Replacement for R?

2016-08-25 Thread Simon Peyton Jones via Glasgow-haskell-users
Sounds bad. But it'll need someone with bytestring expertise to debug. Maybe there's a GHC problem underlying; or maybe it's shortcoming of bytestring. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of

RE: ArgumentDo proposal updated

2016-07-12 Thread Simon Peyton Jones via Glasgow-haskell-users
I've added record construction and update to the syntax, which makes it clearer how the other constructs are analogous to them. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Akio Takano | Sent: 11 July

RE: Rethinking GHC's approach to managing proposals

2016-07-11 Thread Simon Peyton Jones via Glasgow-haskell-users
Just to be clear: * We are actively seeking feedback about the proposal [4] below. It's not a fait-accompli. * You can join the dialogue by (a) replying to this email, (b) via the "Conversations" tab of [4], namely https://github.com/ghc-proposals/ghc-proposals/pull/1 Doubtless via

Simon's email classified as spam

2016-06-19 Thread Simon Peyton Jones via Glasgow-haskell-users
(but perhaps not everyone else)? Thanks Simon | From: Gershom B [mailto:gersh...@gmail.com] | Sent: 18 June 2016 18:53 | To: Simon Peyton Jones <simo...@microsoft.com>; John Wiegley | <jo...@newartisans.com> | Cc: Michael Burge <michaelbu...@pobox.com> | Subject: Re: FW: CM

RE: CMM-to-ASM: Register allocation wierdness

2016-06-18 Thread Simon Peyton Jones
, could you let me know? Thanks Simon From: Takenobu Tani [mailto:takenobu...@gmail.com] Sent: 18 June 2016 08:18 To: Simon Peyton Jones <simo...@microsoft.com> Subject: Re: CMM-to-ASM: Register allocation wierdness Hi Simon, I report to you about your mails. Maybe, your mails don't reach to

RE: CMM-to-ASM: Register allocation wierdness

2016-06-16 Thread Simon Peyton Jones
| All-in-all, the graph coloring allocator is in great need of some love; | Harendra, perhaps you'd like to have a try at dusting it off and perhaps | look into why it regresses in compiler performance? It would be great if | we could use it by default. I second this. Volunteers are sorely

RE: Pattern synonyms and GADTs in GHC 8.0.1

2016-05-26 Thread Simon Peyton Jones
GHC 8.0 swaps the order of provided vs required contexts in a pattern synonym signature. (7.10 was advertised as experimental). Thus: pattern AddP :: () => (Num a, Eq a) => Exp a -> Exp a -> Exp a Then it's fine Simon | -Original Message- | From: Glasgow-haskell-users

RE: suboptimal ghc code generation in IO vs equivalent pure code case

2016-05-16 Thread Simon Peyton Jones
As Harendra has found, the biggest difference is probably that the IO version is necessarily strict, constructing the entire list (via the stack) before it returns, whereas the pure one is lazy, constructing the list only on demand. So the memory footprint of the lazy one will be asymptotically

RE: Looking for GHC compile-time performance tests

2016-05-05 Thread Simon Peyton Jones
Thanks. A repeatable test case would be incredibly helpful here. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Edward Kmett | Sent: 05 May 2016 21:50 | To: Erik de Castro Lopo | Cc:

RE: Magic classes for Overloaded Record Fields, overlaps, FunDeps

2016-04-27 Thread Simon Peyton Jones
| > I have been vacillating between type families and fundeps for the ORF | > classes. I hadn't fully appreciated this point about overlap, but I | > think it is a reason to prefer fundeps, which is the direction in | > which I'm leaning. I'd be grateful for feedback on this issue though! ...

RE: Were usage types ever in GHC

2016-01-22 Thread Simon Peyton Jones
Keith Wansbrough did implement his thesis work in a fork of GHC. But (a) it was jolly complicated and pervasive, and (b) the performance improvements were not great. It didn't pay its way. So we dropped it. See his thesis, available here

RE: suppress warning "Defined but not used: type variable ‘x’" in GHC-8.0

2016-01-18 Thread Simon Peyton Jones
I have created not one but three tickets arising from this thread: · https://ghc.haskell.org/trac/ghc/ticket/11449 · https://ghc.haskell.org/trac/ghc/ticket/11450 · https://ghc.haskell.org/trac/ghc/ticket/11451 I’d love comments on them: which of the three matter most

RE: Warnings, -Wall, and versioning policy

2016-01-13 Thread Simon Peyton Jones
Thanks Gershom. That all sounds fine to me. An implication is that GHC is free to introduce new warnings X into -Wall. Indeed doing so would be good, because the warning X might later move into the default set. Indeed for such warnings, adding a "PS: this warning will become the default

RE: Warnings, -Wall, and versioning policy

2016-01-13 Thread Simon Peyton Jones
OK. When this thread comes to a conclusion, can someone write it down; update the 3-release policy; and say what changes you want in GHC? Thanks Simon | -Original Message- | From: Gershom B [mailto:gersh...@gmail.com] | Sent: 13 January 2016 18:18 | To: Simon Peyton Jones <s

RE: type error formatting

2015-10-24 Thread Simon Peyton Jones
I’m all for it. Can advise. (Make a ticket.) Thanks! Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Evan Laforge Sent: 24 October 2015 03:48 To: GHC users Subject: type error formatting Here's a typical simple type error from GHC:

RE: tweaking text on the ghc downloads page

2015-06-26 Thread Simon Peyton Jones
I’m ok with all of this, but I’d like just to check with Mark L to see how he suggests signposting the HP Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Michael Snoyman Sent: 26 June 2015 15:59 To: Gershom B; Glasgow-Haskell-Users users

RE: overlapping instances in 7.10.1

2015-06-13 Thread Simon Peyton Jones
Sergei I finally found time to look into what is happening here. It's a good illustration of the dangers of overlapping instances. Here is the setup: * Module ResEuc_ * Contains instance (...)= Ring (ResidueE a) (A) instance (..., Ring

7.10 branch

2015-06-11 Thread Simon Peyton Jones
Austin I'm getting these validation failures on the 7.10 branch. Are you? This is on Linux. Simon Unexpected failures: driverT8959a [bad stderr] (normal) ghci/scripts T9878b [bad stderr] (ghci) thT10279 [stderr mismatch] (normal) Unexpected stat failures:

RE: Closed Type Families: separate instance groups?

2015-06-04 Thread Simon Peyton Jones
I think it's pretty good as-is. * Use an open family (with non-overlapping instances) to get yourself into part of the match space: type instance OpenF (Foo b c) = FFoo (Foo b c) * Use a closed family (with overlap and top-to-bottom matching) to deal with that part of the space:

RE: Increased memory usage with GHC 7.10.1

2015-05-01 Thread Simon Peyton Jones
It would be great if someone could · create a ticket for Paolio · investigate what is happening This smaller test case uses Repa, so it’s not clear that GHC is doing anything wrong. Maybe repa is inlining too much? We need insight. Thanks SImon From: Glasgow-haskell-users

RE: Increased memory usage with GHC 7.10.1

2015-05-01 Thread Simon Peyton Jones
Can you open a ticket, please? And put as much data as you can. Using `-dshow-passes` (both for 7.10 and prior versions) and showing the output would be helpful. Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Paolino Sent: 01 May 2015 09:42

RE: SIMD

2015-04-13 Thread Simon Peyton Jones
Geoff Mainland is the originator of the SIMD instruction set work. Let’s see what he says. Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Dominic Steinitz Sent: 11 April 2015 17:45 To: GHC users Subject: SIMD What’s the story with this? I

RE: Typed splices and type checking

2015-04-08 Thread Simon Peyton Jones
Good question! See https://ghc.haskell.org/trac/ghc/ticket/10271. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of J. Garrett Morris | Sent: 27 March 2015 14:30 | To: GHC users | Subject: Typed splices and type

RE: Binary bloat in 7.10

2015-04-06 Thread Simon Peyton Jones
Just to check, can someone summarise the conclusion of this thread? Was it all due to -fsplit-objs? If so, should we add some notes to the user manual to explain what may happen if you use -fsplit-objs? What was the business about Cabal? Simon | -Original Message- | From:

RE: Splices returning splices

2015-03-23 Thread Simon Peyton Jones
Currently it just isn't supported. Suppose you say f x = [| $(g y) |] ...$(f 3) Does $(f 3) mean run (f 3) returning some code with embedded splices, and then run those, or does it mean (as now) call (f 3), and to do so run (g y) first, to generate some code that is spliced into

RE: Qualified names in TH?

2015-03-17 Thread Simon Peyton Jones
What Edward says also applies to code quotations. So, for example: module M import IntSet f :: Q Exp - Q Exp f blah = [| fromList $blah |] module N where import M h x = $(f [| [x,x] |]) The splice expands to (fromList [x,x]), but the fromList guaranteed to be the fromList

GHC 7.10 Prelude: we need your opinion

2015-02-10 Thread Simon Peyton Jones
, libraries, etc etc), so we want to ask your opinion rather than guess it. · Ask Simon Marlow and Simon Peyton Jones to decide which approach to follow for GHC 7.10. Wiki pages have been created summarizing these two primary alternatives, including many more points and counter-points

RE: [Haskell-cafe] GHC 7.10 Prelude: we need your opinion

2015-02-10 Thread Simon Peyton Jones
for. (Which I failed to send the announcement to! I'll fix that.) Simon | -Original Message- | From: Miguel Mitrofanov [mailto:miguelim...@yandex.ru] | Sent: 10 February 2015 15:59 | To: Simon Peyton Jones; hask...@haskell.org; Haskell Cafe (haskell- | c...@haskell.org); GHC users

RE: Proposal: ValidateMonoLiterals - Initial bikeshed discussion

2015-02-05 Thread Simon Peyton Jones
I'm all for it. Syntax sounds like the main difficulty. Today you could use quasiquotatoin [even| 38 |] and get the same effect as $$(validate 38). But it's still noisy. So: what is the non-noisy scheme you want to propose? You don't quite get to that in the wiki page! Simon |

RE: Restricted Template Haskell

2015-02-03 Thread Simon Peyton Jones
). For the latter there is already a page herehttps://wiki.haskell.org/Template_Haskell. I’d really appreciate help with this. Simon From: Greg Weber [mailto:g...@gregweber.info] Sent: 03 February 2015 03:42 To: Simon Peyton Jones Cc: ghc-d...@haskell.org; GHC users; David Terei; Maxwell Swadling Subject: Re

RE: stream fusion, concatMap, exisential seed unboxing

2015-02-02 Thread Simon Peyton Jones
I think it'd help you to open a Trac ticket, give a fully-reproducible test case, including instructions for how to reproduce, and say what isn't happening that should happen. What's odd is that loop_s29q looks strict in its Int arg, yet isn't unboxed. There is a way to get the strictness

RE: Restricted Template Haskell

2015-02-02 Thread Simon Peyton Jones
The new TH is already split into two partshttps://ghc.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal as I’m sure you know · Typed TH is for expressions only, and doesn’t have reify, nor any Q monad. · Untyped TH is the wild west Typed TH may get some of what you

RE: stream fusion, concatMap, exisential seed unboxing

2015-02-02 Thread Simon Peyton Jones
of allocation in your test run instead of 10M. Or something. Simon | -Original Message- | From: Christian Höner zu Siederdissen | [mailto:choe...@tbi.univie.ac.at] | Sent: 02 February 2015 16:02 | To: Simon Peyton Jones | Cc: Glasgow-Haskell-Users | Subject: Re: stream fusion, concatMap

RE: UNPACK Existential datatype

2015-01-23 Thread Simon Peyton Jones
I think this is a very reasonable suggestion. It would take some work to implement, but nothing fundamental. Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Nicholas Clarke Sent: 20 January 2015 13:08 To: glasgow-haskell-users@haskell.org

RE: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread Simon Peyton Jones
Yes, I fixed it on the train. Most helpful. Busy tomorrow but I should have a fix committed by the end of the week Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Richard Eisenberg | Sent: 20 January 2015 16:24

RE: conflicting multi-parameter family instance declarations

2015-01-13 Thread Simon Peyton Jones
Alas it's deliberate. See Section 6 of Closed type families http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/, and the recent thread on https://ghc.haskell.org/trac/ghc/ticket/9918 Maybe you can add your example to that ticket, with some indication of why it's important to

RE: Changes to the type checker with respect to UndecidableInstances

2014-12-30 Thread Simon Peyton Jones
UndecidableInstances is supposed to be needed if GHC can't prove that the instance declarations terminate. But here it can be sure they terminate. GHC 7.6.3 didn't realise this. I'll modify the user manual to be clearer on this point. Simon From: Glasgow-haskell-users

RE: ANNOUNCE: GHC 7.10.1 Release Candidate 1

2014-12-29 Thread Simon Peyton Jones
| If I understand correctly, OverloadedRecordFields has not been merged | yet. Are there any chances to merge it into GHC 7.10.1? I'm afraid not. The situation is that Adam has a fairly complete patch for overloaded record fields, but neither he nor I are happy with it. It makes some fairly

RE: Behavior of touch#

2014-12-16 Thread Simon Peyton Jones
Would it make sense to elaborate the Haddock docs to explain stuff here? Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Carter Schonwald Sent: 16 December 2014 06:45 To: Brandon Simmons Cc: glasgow-haskell-users Subject: Re: Behavior of touch#

RE: Discovery of source dependencies without --make

2014-11-28 Thread Simon Peyton Jones
I have only been skimming this thread, but would it be worth writing a tight specification of what exactly you want? Your original message said only Is there any way to get the dependency discovery of '--make' without the rest, but I really don't know what that means. Nor do I know what you

RE: Discovery of source dependencies without --make

2014-11-28 Thread Simon Peyton Jones
- | From: Lars Hupel [mailto:l...@hupel.info] | Sent: 28 November 2014 14:42 | To: Simon Peyton Jones | Cc: glasgow-haskell-users@haskell.org; Andrey Mokhov | Subject: Re: Discovery of source dependencies without --make | | Rather than explain by deltas from something else, it might

RE: Discovery of source dependencies without --make

2014-11-28 Thread Simon Peyton Jones
ticket. Then if people like it maybe someone can implement it. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Lars Hupel | Sent: 28 November 2014 16:26 | To: Simon Peyton Jones | Cc: glasgow-haskell-users

RE: More flexible literate Haskell extensions (Trac #9789), summary on wiki

2014-11-16 Thread Simon Peyton Jones
page! thanks Simon | -Original Message- | From: Merijn Verstraaten [mailto:mer...@inconsistent.nl] | Sent: 16 November 2014 21:42 | To: Simon Peyton Jones | Cc: ghc-d...@haskell.org; GHC Users Mailing List | Subject: Re: More flexible literate Haskell extensions (Trac #9789), | summary

RE: More flexible literate Haskell extensions (Trac #9789), summary on wiki

2014-11-14 Thread Simon Peyton Jones
Thanks. I don't have strong opinions about any of this. But I would love to have an actual specification of what is proposed. The wiki page starts with Proposal but lists a set of alternatives. Later Concrete proposal discusses only file suffixes, and has lots of discussion of alternatives.

RE: Thread behavior in 7.8.3

2014-10-30 Thread Simon Peyton Jones
I wonder if the knowledge embodied in this thread might usefully be summarised in the user manual? Or on the GHC section of the Haskell wiki https://www.haskell.org/haskellwiki/GHC? Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- |

RE: Type checker plugins

2014-10-17 Thread Simon Peyton Jones
And can someone update the user manual please? | -Original Message- | From: Barney Hilken [mailto:b.hil...@ntlworld.com] | Sent: 17 October 2014 00:14 | To: Carter Schonwald | Cc: Adam Gundry; Eric Seidel; glasgow-haskell-users@haskell.org; Simon | Peyton Jones | Subject: Re: Type

RE: Type checker plugins

2014-10-16 Thread Simon Peyton Jones
This will become easier, I think. look on wip/new-flatten-skoelms-Aug14. I'm now unflattening after solving the flat constraints. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Adam Gundry | Sent: 16

RE: Type checker plugins

2014-10-16 Thread Simon Peyton Jones
-typed.com] | Sent: 16 October 2014 21:50 | To: Eric Seidel; Simon Peyton Jones | Cc: Iavor Diatchki; glasgow-haskell-users@haskell.org | Subject: Re: Type checker plugins | | Thanks Simon, your branch does make it a lot more feasible to unflatten, | so I'll just go ahead and implement that in my plugin

RE: status of rebindable syntax for arrows

2014-10-15 Thread Simon Peyton Jones
| It already has a bug entry: #7828. What would help is to know the | kind of use you have in mind, to see whether it fits with the proposed | solution. Indeed. Moreover #7828 is stalled; it needs some arrow-savvy person to focus cycles on it. If rebindable syntax for arrows is considered

RE: Aliasing current module qualifier

2014-09-30 Thread Simon Peyton Jones
If there is to be such a language feature, I strongly feel it should be via something like module Long.Name.M( f, g, h ) as K where ... I do not want to try to piggy-back on the possible meaning of a self-import; it’s just asking for trouble, as Iavor points out. Using “as M” in

RE: The future of the haskell2010/haskell98 packages - AKA Trac #9590

2014-09-30 Thread Simon Peyton Jones
I hate #1. Let's avoid if unless it's really crucial to some of our users. Simon | -Original Message- | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Austin | Seipp | Sent: 30 September 2014 21:21 | To: ghc-d...@haskell.org; glasgow-haskell-users@haskell.org |

RE: GHC not able to detect impossible GADT pattern

2014-09-03 Thread Simon Peyton Jones
I believe this is probably an instance of https://ghc.haskell.org/trac/ghc/ticket/3927 There are numerous other similar tickets, about GHC's inadequate/misleading warnings for non-exhaustive patterns. A selection is #595, #5728, #3927, #5724, #5762, #4139, #6124, #7669, #322, #8016,

RE: GHC not able to detect impossible GADT pattern

2014-09-03 Thread Simon Peyton Jones
Foo Write s = Writable s Sorry about the egregious bug. Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Merijn Verstraaten | Sent: 03 September 2014 09:22 | To: Simon Peyton Jones | Cc: Tom Schrijvers; GHC Users

RE: Overlapping and incoherent instances

2014-08-07 Thread Simon Peyton Jones
| -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Bertram Felgenhauer | Sent: 07 August 2014 16:25 | To: glasgow-haskell-users@haskell.org | Subject: Re: Overlapping and incoherent instances | | Simon Peyton Jones wrote

RE: Overlapping and incoherent instances

2014-08-05 Thread Simon Peyton Jones
| Here's one concern I have with the deprecation of | -XOverlappingInstances: I don't like overlapping instances, I find | them confusing and weird and prefer to use code that doesn't | include them, because they violate my expectations about how type | classes work. When there is a single

RE: Overlapping and incoherent instances

2014-07-31 Thread Simon Peyton Jones
are for (the old thing still works for now, but it won't do so for ever, and you should change as soon as is convenient). Thanks Simon From: Libraries [mailto:libraries-boun...@haskell.org] On Behalf Of Simon Peyton Jones Sent: 29 July 2014 10:11 To: ghc-devs; GHC users; Haskell Libraries (librar

RE: Overlapping and incoherent instances

2014-07-31 Thread Simon Peyton Jones
: Libraries [mailto:libraries-boun...@haskell.org] On Behalf Of | Andreas Abel | Sent: 31 July 2014 08:59 | To: Simon Peyton Jones; ghc-devs; GHC users; Haskell Libraries | (librar...@haskell.org) | Subject: Re: Overlapping and incoherent instances | | On 31.07.2014 09:20, Simon Peyton Jones wrote

RE: Overlapping and incoherent instances

2014-07-31 Thread Simon Peyton Jones
, OVERLAPS is precisely what you want. I don't care whether it is called OVERLAP or OVERLAPS. So it sounds as if you are content. (I assume you don't want to *prevent* careful programmers from saying something more precise.) Simon | | On 31.07.2014 10:13, Simon Peyton Jones wrote: | Andreas

Overlapping and incoherent instances

2014-07-29 Thread Simon Peyton Jones
Friends One of GHC's more widely-used features is overlapping (and sometimes incoherent) instances. The user-manual documentation is herehttp://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap. The use of overlapping/incoherent instances is controlled

RE: Overlapping and incoherent instances

2014-07-29 Thread Simon Peyton Jones
#-} #endif Show a = Show [a] where ... Simon | -Original Message- | From: Johan Tibell [mailto:johan.tib...@gmail.com] | Sent: 29 July 2014 11:02 | To: Herbert Valerio Riedel | Cc: Niklas Hambüchen; Haskell Libraries (librar...@haskell.org); GHC | users; Simon Peyton Jones; ghc-devs | Subject

RE: Overlapping and incoherent instances

2014-07-29 Thread Simon Peyton Jones
2014 16:56 To: Brandon Allbery Cc: Simon Peyton Jones; Andreas Abel; GHC users; Haskell Libraries (librar...@haskell.org); ghc-devs Subject: Re: Overlapping and incoherent instances How about CAN_OVERLAP? -- Krzysztof 29-07-2014 15:40, Brandon Allbery allber...@gmail.commailto:allber

RE: Overlapping and incoherent instances

2014-07-29 Thread Simon Peyton Jones
question directly, but I think that the behaviour is unchanged from that at present. Simon | | Richard | | On Jul 29, 2014, at 7:02 AM, Simon Peyton Jones simo...@microsoft.com | wrote: | | The current implementation requires the pragma exactly where showed | it. | | I'm not keen on allowing

RE: GhcPlugin-writing and finding things

2014-07-25 Thread Simon Peyton Jones
Philip You are right: there are some missing pieces. * First you need to ask where your plugin's special library module Foo is in the file system. This is what findImportedModule is for, and it seems quite reasonable. However, it (or some variant) should be available to you in CoreM. * Next,

RE: Type family stopped compiling on upgrade from GHC 7.6.3 to 7.8.3

2014-07-22 Thread Simon Peyton Jones
I don't know why 7.6.3 accepts it. 'Float' is a valid type but not a valid kind. For it to be a useful kind we'd need float literal at the type level, and we have no such thing. You can use Nat instead, which does exist at the type level. Simon | -Original Message- | From:

RE: extra ambiguous type variable errors after a couldn't match error?

2014-07-17 Thread Simon Peyton Jones
Good point! See https://ghc.haskell.org/trac/ghc/ticket/9323 Simon | -Original Message- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | boun...@haskell.org] On Behalf Of Evan Laforge | Sent: 17 July 2014 02:32 | To: GHC users | Subject: extra ambiguous type variable

RE: Associated type instances

2014-06-24 Thread Simon Peyton Jones
regretting! But I'm just checking that no one has meanwhile become addicted to it. Simon From: Manuel Chakravarty [mailto:mchakrava...@me.com] Sent: 24 June 2014 08:54 To: Simon Peyton Jones Cc: GHC List; ghc-d...@haskell.org Subject: Re: Associated type instances Simon, I'm not sure when

RE: Associated type instances

2014-06-24 Thread Simon Peyton Jones
Yes I should have said that originally. My proposed change has no loss of expressiveness; at worst you need a helper type family Simon From: Glasgow-haskell-users [mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Richard Eisenberg Sent: 24 June 2014 15:26 To: Simon Peyton Jones

  1   2   3   4   5   6   7   8   9   10   >