Help with fusion rules and such

2014-08-14 Thread David Feuer
I've worked out the basics of how to make more functions from GHC.Base, GHC.List, and Data.List participate in foldr/build fusion, but I could really use some help figuring out how to write the RULES to accompany them. I have too little experience with GHC's simplification process to manage this on

Re: [GHC] #9434: GHC.List.reverse does not fuse

2014-08-15 Thread David Feuer
I'm having trouble when it doesn't fuse—it ends up with duplicate bindings at the top level, because build gets inlined n times, and the result lifted out. Nothing's *wrong* with the code, except that there are multiple copies of it. On Aug 15, 2014 10:58 AM, "GHC" wrote: > #9434: GHC.List.revers

Re: [GHC] #9434: GHC.List.reverse does not fuse

2014-08-15 Thread David Feuer
definition if no fusion happens? > > > On Fri, Aug 15, 2014 at 11:41 AM, David Feuer > wrote: > >> I'm having trouble when it doesn't fuse—it ends up with duplicate >> bindings at the top level, because build gets inlined n times, and the >> result lifted out. No

RE: [GHC] #9434: GHC.List.reverse does not fuse

2014-08-17 Thread David Feuer
plication in the first > place, than to create and try to CSE it away. Others have suggested ways > of doing so, following the pattern of existing RULES. > > > > Simon > > > > *From:* David Feuer [mailto:david.fe...@gmail.com] > *Sent:* 15 August 2014 16:41 >

The definition of cseProgram

2014-08-18 Thread David Feuer
nv1, b') = cseBind env b bs' = cseBinds env1 bs Couldn't we replace all that with the following? (Thanks to Cale for suggesting mapAccumL—I was using scanl because I knew it, but it was not a great fit.) cseProgram = snd . ma

Partial recompilation of libraries

2014-08-18 Thread David Feuer
I'd like to try out a bunch of little changes to the list stuff in base and get some nofib results for each change. Is there a way to do this without recompiling all of GHC each time? ___ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/m

Re: [GHC] #9496: Simplify primitives for short cut fusion

2014-08-22 Thread David Feuer
Yes, I meant "producer" there. On Fri, Aug 22, 2014 at 9:36 AM, GHC wrote: > #9496: Simplify primitives for short cut fusion > -+- > Reporter: dfeuer |Owner: dfeuer > Type:

Why isn't ($) inlining when I want?

2014-08-26 Thread David Feuer
both appear to be saturated. As a result, foldr/build doesn't fire, and full laziness tears things apart. Later on, in simplifier phase 2, $ gets inlined. What's preventing this from happening in the PostGentle phase I added? David Feuer ___ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

Re: Why isn't ($) inlining when I want?

2014-08-27 Thread David Feuer
ned `seq` 1 = 1 but id undefined `seq` 1 = undefined On Wed, Aug 27, 2014 at 12:21 PM, David Feuer wrote: > I just ran that (results attached), and as far as I can tell, it > doesn't even *consider* inlining ($) until phase 2. > > On Wed, Aug 27, 2014 at 4:03 AM, Simon Peyton

Why isn't (.) CONLIKE?

2014-08-28 Thread David Feuer
ill allows them to float, but makes RULES > continue to work even though they’ve been floated. See the user manual. > > > > *From:* Dan Doel [mailto:dan.d...@gmail.com] > *Sent:* 28 August 2014 16:48 > *To:* Simon Peyton Jones > *Cc:* John Lato; David Feuer; ghc-devs > *Sub

Raft of optimizer changes

2014-08-28 Thread David Feuer
On Thu, Aug 28, 2014 at 8:00 AM, simonpj wrote > I've just pushed a bunch of Core-to-Core optimisation changes that have been > sitting in my tree for ages. The aggregate effect on nofib is very modest, > but they are mostly aimed at corner cases, and consolidation. Thanks for trying to do th

RE: Fusion

2014-08-29 Thread David Feuer
the problem you > describe > https://ghc.haskell.org/trac/ghc/wiki/Debugging/TickyTicky > > Simon > > | -Original Message- > | From: David Feuer [mailto:david.fe...@gmail.com] > | Sent: 20 August 2014 09:33 > | To: Simon Peyton Jones > | Subject: Re: Fusion > | &g

Re: Why isn't ($) inlining when I want?

2014-08-29 Thread David Feuer
On Thu, Aug 28, 2014 at 6:22 AM, Simon Peyton Jones wrote: > Oh, now I understand. In > > loop g = sum . map g $ [1..100] > > GHC can share [1..10] across all calls to loop, although that nixes > fusion. Because each call of loop may have a different g. > > But in > > loop' = sum

cons/build and making rules look boring

2014-08-30 Thread David Feuer
I think I may have figured out at least part of the reason that cons/build gives bad results. I actually ran into a clue when working on scanl. It seems at least part of the problem is that a rule like x : build g = build (\c n -> c x (g c n)) makes (:) look "interesting" to the inliner. Unfortun

Trouble compiling fibon

2014-08-31 Thread David Feuer
I'm trying to compile the fibon benchmark suite, but I'm getting a non-specific permission error. Can anyone give me a clue? == make boot - --no-print-directory; in /home/dfeuer/src/ghc-slowmod/nofib/fibon/Hackage/Bzlib //

RE: cons/build and making rules look boring

2014-09-01 Thread David Feuer
te example brings tremendous focus > to discussions, giving readers something specific to bite on.) > > Simon > > | -Original Message- > | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of David > | Feuer > | Sent: 30 August 2014 23:05 > | To: ghc-devs

Trying to fix an efficiency issue noted in a TODO in SAT.hs

2014-09-06 Thread David Feuer
cture down before choosing the best data structure. Thanks, David Feuer diff --git a/compiler/simplCore/SAT.lhs b/compiler/simplCore/SAT.lhs index a0b3151..aae3e69 100644 --- a/compiler/simplCore/SAT.lhs +++ b/compiler/simplCore/SAT.lhs @@ -67,10 +67,16 @@ import VarSet import Unique import Un

Re: Trying to fix an efficiency issue noted in a TODO in SAT.lhs

2014-09-07 Thread David Feuer
Joachim Breitner wrote: > Did you profile first, and did it show up there? You know, premature > optimization... so it might be that your fix is a nice improvement and > useful exercise (and very welcome as such), but without much real-world > effect. You're right, of course. I read the comment a

What is testsuite/tests/rename/should_fail/rnfail018.hs supposed to test?

2014-09-08 Thread David Feuer
proto; the parens after the for-all fooled it class Monad m => StateMonad s m where getState :: m s setState0 :: forall b. (StateMonad (a,b) m => m a) setState0 = getState >>= \ (l,_r) -> return l David Feuer ___ ghc-devs mailing list

Re: The list fusion lab

2014-09-11 Thread David Feuer
Joachim Breitner wrote: > Together with John Wiegly at ICFP, I started to create a list > performance laboratory. You can find it at: > https://github.com/nomeata/list-fusion-lab Many thanks to you both! This sounds like an excellent idea. I do hope someone figures out a way around the cri

Re: FoldrW/buildW issues

2014-09-12 Thread David Feuer
On Sep 12, 2014 2:35 PM, "Joachim Breitner" wrote: > Interesting. I assumed that some wrap.unwrap=id law would hold, or at > least some moral approximation (e.g. disregarding bottoms in an > acceptable manner). But if the wrappers have to do arbitrary stuff that > can arbitrarily interact with how

Re: FoldrW/buildW issues

2014-09-14 Thread David Feuer
Joachim Breitner wrote: > Am Samstag, den 13.09.2014, 00:01 -0400 schrieb David Feuer: > > On Sep 12, 2014 2:35 PM, "Joachim Breitner" > > wrote: > > > Interesting. I assumed that some wrap.unwrap=id law would hold, or > > at > > > least some mor

Re: FoldrW/buildW issues

2014-09-14 Thread David Feuer
ctly. David On Sun, Sep 14, 2014 at 2:08 PM, Dan Doel wrote: > Which scanl wrapper are you referring to? > > The first one I figured out was quite wrong in certain ways. But I think > the new one is less controversial; it's a lot like the reverse one. > > On Sun, Sep 14,

Cleaning up rather silly static arguments

2014-09-15 Thread David Feuer
Aside from anything having to do with the foldrW/buildW stuff, I decided to try a little experiment using fusing scanl and reverse (implementations at http://lpaste.net/2416758997739634688 ) When I define scanr f b = reverse . scanl (flip f) b . reverse I get this: scanr1 scanr1 = \ @ a_akP _ e

Where can I stick a dead code elimination rule for quotRemInt#?

2014-09-19 Thread David Feuer
As I describe in #9617, GHC's CSE in 7.9 seems to be good enough to let Int and Integer use quot x y = fst (x `quotRem` y) rem x y = snd (x `quotRem` y) And actually get good results in code that uses both the quotient and the remainder. I believe the only thing left to be able to actually implem

FFI library error building GHC

2014-09-19 Thread David Feuer
I keep getting this error. Can anyone help? I tried removing the file as suggested, but it made no difference. "/home/dfeuer/GHC/7.8.3.bin/bin/ghc" -o utils/genapply/dist/build/tmp/genapply -hisuf hi -osuf o -hcsuf hc -static -O -H64m -package pretty -package-db libraries/bootstrapping.conf -i

Re: FFI library error building GHC

2014-09-20 Thread David Feuer
, and hence the > libffi.a was in libffi/build/inst/lib64/libffi.a iirc. > > On Sep 20, 2014, at 8:13 AM, David Feuer wrote: > > > I keep getting this error. Can anyone help? I tried removing the file as > suggested, but it made no difference. > > > > "/h

Re: ghc-devs Digest, Vol 133, Issue 40

2014-09-23 Thread David Feuer
Simon Peyton Jones wrote: > anywhere, I think. You might want a new HsSyn data type for "list with > possible leading or trailing commas": > > data HsCommadList a > = HCL > Int -- Number of leading commas > [a] > Int -- Number of trailing commas > If we're going

Re: FoldrW/buildW issues

2014-09-24 Thread David Feuer
On Sep 12, 2014 2:35 PM, "Joachim Breitner" wrote: > I once experimented with a magic "oneShot :: (a -> b) -> (a -> b)" > function, semantically the identity, but tell the compiler not to share > the result of the computation. Using that in the definition of > foldl-as-foldr, one can get the same

Re: dropWhileEndLE breakage

2014-10-02 Thread David Feuer
t error message—the difference in behavior doesn't matter there. David Feuer ___ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

oneShot (was Re: FoldrW/buildW issues)

2014-10-07 Thread David Feuer
Just for the heck of it, I tried out an implementation of scanl using Joachim Breitner's magical oneShot primitive. Using the test scanlA :: (b -> a -> b) -> b -> [a] -> [b] scanlA f a bs = build $ \c n -> a `c` foldr (\b g x -> let b' = f x b in (b' `c` g b')) (const n)

Re: oneShot (was Re: FoldrW/buildW issues)

2014-10-07 Thread David Feuer
Yes, and it does a very good job in many cases. In other cases, it's not as good. On Tue, Oct 7, 2014 at 7:59 AM, Sophie Taylor wrote: > Wait, isn't call arity analysis meant to do this by itself now? > > On 7 October 2014 17:05, David Feuer wrote: >> >> Just for

T3064 failures

2014-10-16 Thread David Feuer
I don't know what's going on, but T3064 is giving some substantial performance trouble, making all the validations fail: max_bytes_used value is too high: ExpectedT3064(normal) max_bytes_used: 13251728 +/-20% Lower bound T3064(normal) max_bytes_used: 10601382 Upper bound T3064(norm

Avoiding the hazards of orphan instances without dependency problems

2014-10-19 Thread David Feuer
Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-19 Thread David Feuer
place, and then modify an imported module later. On Oct 19, 2014 1:05 PM, "Brandon Allbery" wrote: > On Sun, Oct 19, 2014 at 1:02 PM, David Feuer > wrote: > >> with a flag -XAllowForbiddenInstancesAndInviteNasalDemons >> > > One could argue this is spelled -X

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-19 Thread David Feuer
nt, but I think > it's feasible (perhaps in a restricted manner). > > I think I'd prefer this when implementing orphan instances, and probably > when writing the pragmas as well. > > On Mon, Oct 20, 2014 at 1:02 AM, David Feuer > wrote: > >> Orphan instance

Help understanding Specialise.lhs

2014-10-19 Thread David Feuer
ight be able to help me get enough of a sense of it to let me do what I need? Many thanks in advance. David Feuer ___ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-19 Thread David Feuer
only requires c. Also your method seems to > require having both the class and type in scope, in which case one could > simply declare the instance in that module anyway. > > On Mon, Oct 20, 2014 at 9:29 AM, David Feuer > wrote: > >> I don't think your approach is fle

RE: Help understanding Specialise.lhs

2014-10-20 Thread David Feuer
On Oct 20, 2014 5:05 AM, "Simon Peyton Jones" wrote: > I’m unclear what you are trying to achieve with #9701. I urge you to write a clear specification that we all agree about before burning cycles hacking code. What I'm trying to achieve is to make specialization work in a situation where it cu

Re: Help understanding Specialise.lhs

2014-10-20 Thread David Feuer
d produce GHC.Num.$fNumInt_$c+. But for some reason, GHC fails to recognize and exploit this fact! I would like help understanding why that is, and what I can do to fix it. On Mon, Oct 20, 2014 at 7:53 AM, David Feuer wrote: > On Oct 20, 2014 5:05 AM, "Simon Peyton Jones" > wrote: &g

Re: Help understanding Specialise.lhs

2014-10-20 Thread David Feuer
en maybe we can > find a mutually convenient time. > > > > Do you have reason to suppose that the pattern you describe below is > common? That is, if implemented, would it make a big difference to > programs we care about? > > > > Simon > > > > *From

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-21 Thread David Feuer
As I said before, it still doesn't solve the problem I'm trying to solve. Look at a package like criterion, for example. criterion depends on aeson. Why? Because statistics depends on it. Why? Because statistics wants a couple types it defines to be instances of classes defined in aeson. John Lato'

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-21 Thread David Feuer
On Oct 21, 2014 1:22 PM, "John Lato" wrote: > > Perhaps you misunderstood my proposal if you think it would prevent anyone else from defining instances of those classes? Part of the proposal was also adding support to the compiler to allow for a multiple files to use a single module name. That m

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-22 Thread David Feuer
e classes? Part of the > > > proposal was also adding support to the compiler to allow for a > multiple > > > files to use a single module name. That may be a larger technical > > > challenge, but I think it's achievable. > > > > > > I think one key differ

Re: Avoiding the hazards of orphan instances without dependency problems

2014-10-22 Thread David Feuer
mas are not a good solution, while control of imports and > exports is. Unless the > problems turn out to be impossible to overcome. > > Janek > > Dnia środa, 22 października 2014, David Feuer napisał: > > You're not the first one to come up with this idea (and I don't

Improving specialization, redux

2014-10-24 Thread David Feuer
I spoke with Simon today, and I think I have a bit of a better idea now of what's going on with specialization, and why it sometimes fails to specialize things as much as it could. Apparently, the replacement of (sel @ type dict) by sel.type is accomplished by the use of a rewrite rule generated by

Re: Call Arity, oneShot, or both

2014-10-26 Thread David Feuer
> There is also the option of combining both. Then we do not get the > regression, but still the improvement for fft2: I *definitely* think we should leave Call Arity in place by default unless and until something strictly better comes along. One very nice feature is that it works for a lot of use

Re: Call Arity, oneShot, or both

2014-10-27 Thread David Feuer
Joachim Breitner כתב That would be great! But do we have evidence of this user-written code > that benefits? So far I have only seen relevant improvement due to > list-fusion a left-foldish function. > I was under the impression that the transformation was much more general than that, improving v

Re: Call Arity, oneShot or both

2014-10-28 Thread David Feuer
Simon Peyton Jones wrote: > > But since it is plausible that there are cases out there where it might > help, even if just a little, we could go forward ?unless the > implementation becomes ugly. > Based on our experience with Call Arity, it's much more likely that it will help a lot in a few ca

Is USE_REPORT_PRELUDE still useful?

2014-10-28 Thread David Feuer
A lot of code in GHC.List and perhaps elsewhere compiles differently depending on whether USE_REPORT_PRELUDE is defined. Not all code differing from the Prelude implementation. Furthermore, I don't know to what extent, if any, such code actually works these days. Some of it certainly was not usable

Re: Understanding core2core optimisation pipeline

2014-10-30 Thread David Feuer
On Thu, Oct 30, 2014 Jan Stolarek wrote: > > 2. First pass of full laziness is followed by floating in. At that stage > we have not yet run the > demand analysis and yet the code that does the floating-in checks whether > a binder is one-shot > (FloatIn.okToFloatInside called by FloatIn.fiExpr Ann

thenIO removal

2014-11-02 Thread David Feuer
GHC.Base has a function, thenIO, that isn't used anywhere in the libraries or compiler, and isn't exported anywhere "public". But for some reason, it's listed in compiler/prelude/PrelNames.lhs, which causes a validation failure if I remove it. Is there a reason that a completely unused function is

RE: thenIO removal

2014-11-03 Thread David Feuer
Simon Peyton Jones wrote: > > It's not a big deal. > > You can probably replace both those bindIOName uses with bindMName (i.e > (>>=)), in TcRnDriver. That will just make GHCi generate code with uses of > overloaded (>>=) that must be evaluated, rather than calling bindIO > directly. It should

Re: RFC: Dropping Windows XP support

2014-11-07 Thread David Feuer
+1. Windows XP was Microsoft's most successful OS thus far, but it's pretty much dead now. One potentially related potential concern: how will this change affect Wine support? On Fri, Nov 7, 2014 at 1:16 PM, Austin Seipp wrote: > Hi all, > > This is a quick discussion about the current system re

Re: Reviving the LTS Discussions (ALT: A separate LTS branch)

2014-11-07 Thread David Feuer
GHC is an open source project. People work on it because 1. They enjoy it and find it interesting, 2. They need it to work well to support their own software, 3. They're trying to write a paper/get a degree/impress their peers, or, in very rare cases, 4. Someone pays them to do it. People are also

Re: [GHC] #9781: Make list monad operations fuse

2014-11-11 Thread David Feuer
On Nov 11, 2014 3:56 AM, "Kim-Ee Yeoh" wrote: > > From the patch fragment at > > https://phabricator.haskell.org/D455?id=1311#inline-3123 > > What's the justification for expanding out the definition of mapM from "sequence . map f" into do-notation and duplicated code? > > Observe how mapM now dup

RE: [GHC] #9781: Make list monad operations fuse

2014-11-11 Thread David Feuer
On Nov 11, 2014 6:04 AM, "Simon Peyton Jones" wrote: > It’s true that, particularly for fusion, inlining can make a huge difference. And GHC really does need help… it’s extremely hard for it to make the “right” choice all the time. The inliner does indeed do amazing things, and list fusion does

RE: [GHC] #9781: Make list monad operations fuse

2014-11-11 Thread David Feuer
away from our consumer, they will not fuse. I think Simon's simplifier changes a few months ago helped with this issue, but I don't know that it is (or can ever be) resolved completely. On Nov 11, 2014 11:54 AM, "David Feuer" wrote: > > On Nov 11, 2014 6:04 AM, "Si

Re: The future of the Haskell98 and Haskell2010 packages

2014-11-18 Thread David Feuer
I think you're right, and that's a strong reason to come up with an update to the Haskell Report. Include in it, at least: -- Big-ticket items 0. Monoid 1. Foldable, Traversable 2. Applicative 3. Applicative => Monad -- side notes 4. inits = map reverse . scanl (flip (:)) [] -- efficiency—not opt

seq#: do we actually need it as a primitive?

2015-01-07 Thread David Feuer
I've read about the inlining issues surrounding Control.Exception.evaluate that seem to have prompted the creation of seq#, but I'm still missing something. Isn't seq# a sthe same as let !a' = a in (# s, a' #) ? David ___ ghc-devs mailing list ghc

Re: seq#: do we actually need it as a primitive?

2015-01-08 Thread David Feuer
On Thu, Jan 8, 2015 at 8:42 AM, Roman Cheplyaka wrote: > Also, where can I find the 'instance Monad IO' as understood by GHC? > grep didn't find one. It's in GHC.Base. ___ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listin

Milestones

2015-01-09 Thread David Feuer
I took the liberty of pushing back the milestones for a few tickets that looked unlikely to be acted on for 7.10.1, based on a combination of severity, recent activity, and perceived intrusiveness. If anyone objects, please move them back. #9314: Each object file in a static archive file (.a) is l

Re: vectorisation code?

2015-01-19 Thread David Feuer
Richard Eisenberg wrote: > Here's an alternate suggestion: in SimplCore, keep the call to vectorise around, but commented out (not just with CPP, for better syntax highlighting). Include a Note explaining what `vectorise` does and why it's not there at the moment. However, move the actual vectorisa

Re: GHC support for the new "record" package

2015-01-26 Thread David Feuer
>> I don?t think anyone is suggesting adding any of lens are they? Which >> bits did you think were being suggested for addition? >> > I was mostly referring to the use of the (a -> f b) -> s -> f t form. All right. If nobody's suggesting it, I'll suggest it. Is it really that evil? Why does it o

What is the story behind the type of undefined?

2015-02-01 Thread David Feuer
If I define {-# LANGUAGE MagicHash #-} g :: Int# -> Int g 3# = 3 myUndefined = undefined then this gives a sensible type error about a kind mismatch: usual :: Int usual = g myUndefined but this, oddly enough, compiles: peculiar :: Int peculiar = g undefined GHCi and the definition in GHC.Er

Re: What is the story behind the type of undefined?

2015-02-01 Thread David Feuer
> polymorphism, but it hasn't been implemented yet. See > https://ghc.haskell.org/trac/ghc/wiki/NoSubKinds for more details.) > > Hope this helps, > > Adam > > > On 01/02/15 18:54, David Feuer wrote: >> If I define >> >> {-# LANGUAGE MagicHash

Merge FlexibleContexts with FlexibleInstances?

2015-02-05 Thread David Feuer
In my limited experience thus far, it seems to me that a substantial majority of modules that start out needing one of these end up needing the other one too. They appear to be two sides of the same coin, each allowing for (slightly) more powerful termination checking. Should the two just be made s

Re: Behavior change of Data.Char

2015-02-18 Thread David Feuer
7.10 uses a newer version of Unicode, which could explain differences. On Thu, Feb 19, 2015 at 12:19 AM, Kazu Yamamoto wrote: > Hi, > > It seems to me that some characters of GHC 7.10.1RC2 behave > differently from those of GHC 7.8.4: > > 7.8.4 7.10.1RC2 > isLower (cha

Re: Behavior change of Data.Char

2015-02-20 Thread David Feuer
I don't think so. There's no guarantee that future versions will maintain it, and I don't know that we want to take responsibility for continually checking on that. David On Feb 20, 2015 Simon Peyton Jones wrote: > It'd be good to document this condition/invariant in the Haddocks, wouldn't it?! >

Proposal: Turn on ScopedTypeVariables by default

2015-02-23 Thread David Feuer
I know this will be controversial, because it can break (weird) code and because it's not Haskell 2010, but hey, you can't make brain salad without breaking a few heads. ScopedTypeVariables is just awesome for two fundamental reasons: 1. It lets you write type signatures for more things. 2. It let

More at-use-site extension pragmas please

2015-03-15 Thread David Feuer
For people working on libraries intended to be portable but using/offering GHC specials when compiled with GHC, it's nice to be able to verify quickly that nothing relies on a GHC extension that shouldn't. For example, I just submitted a pull request to add an IsString instance to Data.Sequence: i

Re: [Haskell-cafe] Generalized Newtype Deriving not allowed in Safe Haskell

2015-04-10 Thread David Feuer
I think a module exporting some but not all data constructors of a type is fundamentally broken behavior. I would generally be in favor of prohibiting it altogether, and I would be strongly opposed to letting continued support for it break anything else. On Apr 10, 2015 9:05 AM, "Douglas McClean"

Re: MonadFail proposal (MFP): Moving fail out of Monad

2015-06-11 Thread David Feuer
Pattern matching on `undefined` is not like pattern match failure. Single-constructor types are only special if they're unlifted: `newtype` and GHC's unboxed tuples are the only examples I know of, and you can't use unboxed tuples in this context. On Thu, Jun 11, 2015 at 11:28 AM, Wolfgang Jeltsch

Access to class defaults and derived instances

2015-08-22 Thread David Feuer
>From time to time, a library lacks an instance for something that I want. For example, I may need to convert data Foo = Bar (Vector Baz) to FishFood, but (to avoid unreasonable dependencies) Vector doesn't have a ToFishFood instance, so I can't just write instance ToFishFood Foo and (using Gen

Re: Access to class defaults and derived instances

2015-08-24 Thread David Feuer
I have a hard time fully understanding this request without more context. > But I do think I understand the last paragraph. And it seems bound to > create class incoherence. What if someone else *does* write that orphan > instance you're avoiding writing? > > Richard > > On A

Deriving Contravariant and Profunctor

2015-09-11 Thread David Feuer
Would it be possible to add mechanisms to derive Contravariant and Profunctor instances? As with Functor, each algebraic datatype can only have one sensible instance of each of these. David Feuer ___ ghc-devs mailing list ghc-devs@haskell.org http

Re: Deriving Contravariant and Profunctor

2015-09-11 Thread David Feuer
vestigated adding TH code-generation for the contravariant package, and > ultimately rejected it on these grounds. > > https://github.com/ekmett/contravariant/issues/17 > > -Edward > > > > On Fri, Sep 11, 2015 at 12:49 PM, David Feuer wrote: >> >> Would it be p

MIN_VERSION macros

2015-09-25 Thread David Feuer
he version based on the GHC version. This works reasonably well for base, ghc-prim, containers, etc., but not so well/at all for others. Would there be some way to get GHC itself to provide these macros to all modules that request CPP? David Feuer __

Context for typed holes

2015-10-08 Thread David Feuer
Unless something has changed really recently that I've missed, the typed holes messages are missing some really important information: instance information for types in scope. When I am trying to fill in a hole, I look to the "relevant bindings" to show me what pieces I have available to use. Those

Moving forall with coerce

2015-10-19 Thread David Feuer
It appears, as far as I can tell, that GHC can't move a forall past an -> with coerce. I was playing around with the MonadTrans instance for Codensity, wanting (essentially) to write lift = coerce (>>=) This is legal: instance MonadTrans Codensity where lift = frob frob :: forall m a . Monad m

Coercion logic

2015-10-22 Thread David Feuer
exactly the same run-time representation, and because People Wiser Than Me believe Coercible should *always* remain symmetric. My (admittedly reptilian) brain wonders what it would take to tell the type checker that forall a b . Coercible a b ~ Coercible b a and have it over with. David Feuer

Re: Coercion logic

2015-10-22 Thread David Feuer
hat (Coercible a b > <=> Coercible b a). Do you have a concrete example of where it's not doing > this? Have you tested against HEAD? > > Thanks, > Richard > > On Oct 22, 2015, at 9:56 AM, David Feuer wrote: > >> At present, any time we write a function w

Re: Context for typed holes

2015-10-22 Thread David Feuer
T Chakravarty" > wrote: > > > > I think, this is a good point. Maybe you should make a ticket for it. > > #9479, I think. > > Cheers, > Andres > > >> David Feuer : > >> > >> Unless something has changed really recently that I'v

Re: Context for typed holes

2015-10-22 Thread David Feuer
> > On Oct 23, 2015 1:28 AM, "Andres Löh" wrote: > >> > >> Hi. > >> > >> On Oct 23, 2015 01:15, "Manuel M T Chakravarty" > >> wrote: > >> > > >> > I think, this is a good point. Maybe you should mak

Allow ambiguous types (with warning) by default

2015-12-05 Thread David Feuer
The ambiguity check produces errors that are quite surprising to the uninitiated. When the check is suppressed, the errors at use sites are typically much easier to grasp. On the other hand, there's obviously a lot of value to catching mistakes as soon as possible. Would it be possible to turn that

Re: ambiguous type stuff

2015-12-05 Thread David Feuer
I think I didn't explain myself well enough. I'm not talking about expanded defaulting, although that may be tied up with the same mechanisms. Perhaps the best thing is just to work on the error message text for certain ambiguous type situations. Notably, situations where adding a proxy argument or

Re: Allow ambiguous types (with warning) by default

2015-12-05 Thread David Feuer
about if they are > doing something wrong at the definition site or the call site. With the > status quo it complains at the right time that you aren't going to sit there > flailing around trying to fix a call site that can never be fixed. > > -Edward > > On Sat,

Re: Allow ambiguous types (with warning) by default

2015-12-05 Thread David Feuer
ting the code that can't be called you may never > see the warning. It'll be tucked away in a cabal or stack build log > somewhere. > > -Edward > > On Sun, Dec 6, 2015 at 12:06 AM, David Feuer wrote: >> >> No, I want it to *warn* by default. If I write >

RE: Allow ambiguous types (with warning) by default

2015-12-08 Thread David Feuer
2:13 AM, Edward Kmett > | wrote: > | > If you aren't the one writing the code that can't be called you may > | > never see the warning. It'll be tucked away in a cabal or stack > | build > | > log somewhere. > | > > | > -Edward > | &g

Non-exported class constraints in errors

2015-12-08 Thread David Feuer
The latest implementation of Data.Constraint.Forall uses type family Forall (p :: k -> Constraint) :: Constraint where Forall p = Forall_ p class p (Skolem p) => Forall_ (p :: k -> Constraint) instance p (Skolem p) => Forall_ (p :: k -> Constraint) The trouble is that errors relating to Forall

Type class for sanity

2016-01-24 Thread David Feuer
Since type families can be stuck, it's sometimes useful to restrict things to sane types. At present, the most convenient way I can see to do this in general is with Typeable: type family Foo x where Foo 'True = Int class Typeable (Foo x) => Bar x where blah :: proxy x -> Foo x This will pre

Re: Type class for sanity

2016-01-24 Thread David Feuer
nce impossible to produce, but the possibility of stuckness defeats it as its currently written. On Jan 25, 2016 1:01 AM, "Jeffrey Brown" wrote: > "Stuck type" is proving difficult to Google. Do you recommend any > references? > > On Sun, Jan 24, 2016 at 1:24 PM, Da

Re: Type class for sanity

2016-01-25 Thread David Feuer
ggest a different name. Ground? Terminating? NormalForm? > Irreducible? ValueType? I don't love any of these, but I love Sane less. > > On Jan 24, 2016, at 4:24 PM, David Feuer wrote: > > > Since type families can be stuck, it's sometimes useful to restrict > > thi

Re: Type class for sanity

2016-01-25 Thread David Feuer
You're correct. Please forget that name. On Jan 25, 2016 12:33 PM, "wren romano" wrote: > On Mon, Jan 25, 2016 at 7:34 AM, Richard Eisenberg > wrote: > > But I suggest a different name. Ground? Terminating? NormalForm? > Irreducible? ValueType? I don't love any of these, but I love Sane less. >

Re: Dropping bzip2 release tarballs?

2016-02-01 Thread David Feuer
Does this really strain storage infrastructure? There are only a few blobs per release. If that's really a problem, sufficiently ancient ones can presumably be pruned down to a single format without too many complaints (e.g., if someone wants GHC 7.6, they may not be able to have their choice of fo

Missing definitions of associated types

2016-02-18 Thread David Feuer
It seems to be that a missing associated type definition should be an error, by default, rather than a warning. The current behavior under those circumstances strikes me as very strange, particularly for data families and particularly in the presence of overlapping. {-# LANGUAGE TypeFamilies #-} c

Re: Missing definitions of associated types

2016-02-18 Thread David Feuer
ng as overlapping instances in their present form are around. On Feb 18, 2016 12:49 PM, "Reid Barton" wrote: > Well, I see your point; but you also can't define a > > On Thu, Feb 18, 2016 at 12:00 PM, David Feuer > wrote: > >> It seems to be that a missing associa

Pattern synonym thoughts

2016-02-24 Thread David Feuer
There are two features I think would make pattern synonyms even nicer: 1. If a pattern synonym is defined in the same module as one of the type constructors in the type of thing it matches, then it should be possible to export it "attached" to one or more of those constructors (normally but not ne

Could we promote unlifted tuples?

2016-03-19 Thread David Feuer
unlifted tuple types can be used would presumably translate directly to restrictions on how types of unlifted tuple kind can be used. David Feuer ___ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Pattern synonym type flexibility

2016-04-20 Thread David Feuer
As far as I can tell from the 7.10 documentation, it's impossible to make a bidirectional pattern synonym used as a constructor have a different type signature than when used as a pattern. Has this been improved in 8.0? I really want something like class FastCons x xs | xs -> x where fcons :: x

  1   2   3   4   >