From omeragacan at gmail.com Wed Jun 1 07:31:32 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Wed, 1 Jun 2016 03:31:32 -0400 Subject: Core of a whole package In-Reply-To: References: Message-ID: You have to do your manipulations module by module, as GHC is doing compilation that way. If you need some information from other modules when compiling a module, you should dump that information in .hi files (like definitions of inline functions). What exactly are you trying to do? 2016-05-31 17:56 GMT-04:00 Alberto Sadde O. : > >> >> 2016-05-31 16:04 GMT-04:00 Alberto Sadde O. : >> > I am trying to get the Core of a whole package. >> > I have been using the GHC API to get the Core of each file in a package >> > but >> > I have a problems with non-exposed modules of the package. >> >> Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You >> should see Core outputs under `dist/`. >> (or `cabal configure --ghc-options=...` then `cabal build`) >> >> If you have all the dependencies installed already you can just do >> `ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where >> `Main.hs` imports all the modules in your project. > > > Thanks for the answer. > The thing is that I want to manipulate the Core of the package not just > simply dump it to a file. > > > From albertosadde at gmail.com Wed Jun 1 07:35:50 2016 From: albertosadde at gmail.com (Alberto Sadde O.) Date: Wed, 1 Jun 2016 08:35:50 +0100 Subject: Core of a whole package In-Reply-To: References: Message-ID: I am trying to extract information at the Core level about which functions are the most used within a package, which data types are the most used. So how do I dump the contents of a module to a .hi file? Is this something I can do through the API? Alberto On Wed, Jun 1, 2016 at 8:31 AM, ?mer Sinan A?acan wrote: > You have to do your manipulations module by module, as GHC is doing > compilation > that way. If you need some information from other modules when compiling a > module, you should dump that information in .hi files (like definitions of > inline functions). > > What exactly are you trying to do? > > 2016-05-31 17:56 GMT-04:00 Alberto Sadde O. : > > > >> > >> 2016-05-31 16:04 GMT-04:00 Alberto Sadde O. : > >> > I am trying to get the Core of a whole package. > >> > I have been using the GHC API to get the Core of each file in a > package > >> > but > >> > I have a problems with non-exposed modules of the package. > >> > >> Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You > >> should see Core outputs under `dist/`. > >> (or `cabal configure --ghc-options=...` then `cabal build`) > >> > >> If you have all the dependencies installed already you can just do > >> `ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where > >> `Main.hs` imports all the modules in your project. > > > > > > Thanks for the answer. > > The thing is that I want to manipulate the Core of the package not just > > simply dump it to a file. > > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Wed Jun 1 08:38:40 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Wed, 1 Jun 2016 04:38:40 -0400 Subject: Core of a whole package In-Reply-To: References: Message-ID: > So how do I dump the contents of a module to a .hi file? Is this > something I can do through the API? I'm not saying you can at the moment, I'm just saying usually if you need some cross-module sharing you put the stuff you want to read when compiling other files in .hi files as those files are read when compiling other modules. In you case I think you can just keep a file, write your module-level stats there and then run a post-compilation pass to generate final stats. 2016-06-01 3:35 GMT-04:00 Alberto Sadde O. : > I am trying to extract information at the Core level about which functions > are the most used within a package, which data types are the most used. > > So how do I dump the contents of a module to a .hi file? Is this something I > can do through the API? > > > > Alberto > > > On Wed, Jun 1, 2016 at 8:31 AM, ?mer Sinan A?acan > wrote: >> >> You have to do your manipulations module by module, as GHC is doing >> compilation >> that way. If you need some information from other modules when compiling a >> module, you should dump that information in .hi files (like definitions of >> inline functions). >> >> What exactly are you trying to do? >> >> 2016-05-31 17:56 GMT-04:00 Alberto Sadde O. : >> > >> >> >> >> 2016-05-31 16:04 GMT-04:00 Alberto Sadde O. : >> >> > I am trying to get the Core of a whole package. >> >> > I have been using the GHC API to get the Core of each file in a >> >> > package >> >> > but >> >> > I have a problems with non-exposed modules of the package. >> >> >> >> Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You >> >> should see Core outputs under `dist/`. >> >> (or `cabal configure --ghc-options=...` then `cabal build`) >> >> >> >> If you have all the dependencies installed already you can just do >> >> `ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where >> >> `Main.hs` imports all the modules in your project. >> > >> > >> > Thanks for the answer. >> > The thing is that I want to manipulate the Core of the package not just >> > simply dump it to a file. >> > >> > >> > > > From tkn.akio at gmail.com Wed Jun 1 11:48:31 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Wed, 1 Jun 2016 11:48:31 +0000 Subject: Moving ArgumentsDo forward Message-ID: Hi, Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would love to see in GHC. It's a small syntactic extension that allows do, case, if and lambda blocks as function arguments, without parentheses. However, its differential revision [1] has been abandoned, citing a mixed response from the community. A message [2] on the ticket summarizes a thread in haskell-cafe on this topic. I, for one, think adding this extension is worthwhile, because a significant number of people support it. Also, given how some people seem to feel ambivalent about this change, I believe actually allowing people to try it makes it clearer whether it is a good idea. Thus I'm wondering: is there any chance that this gets merged? If so, I'm willing to work on whatever is remaining to get the change merged. Regards, Takano Akio [0]: https://ghc.haskell.org/trac/ghc/ticket/10843 [1]: https://phabricator.haskell.org/D1219 [2]: https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 From eir at cis.upenn.edu Wed Jun 1 12:13:12 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Wed, 1 Jun 2016 08:13:12 -0400 Subject: Parser changes for supporting top-level SCC annotations In-Reply-To: References: Message-ID: <82C83F49-4D45-4118-B0AC-5C687F931206@cis.upenn.edu> What about just using a new pragma? > {-# SCC_FUNCTION f "f_scc" #-} > f True = ... > f False = ... The pragma takes the name of the function (a single identifier) and the name of the SCC. If you wish both to have the same name, you can leave off the SCC name. It seems worth it to me to introduce a new pragma here. Richard On May 30, 2016, at 3:14 PM, ?mer Sinan A?acan wrote: > I'm trying to support SCCs at the top-level. The implementation should be > trivial except the parsing part turned out to be tricky. Since expressions can > appear at the top-level, after a {-# SCC ... #-} parser can't decide whether to > reduce the token in `sigdecl` to generate a `(LHsDecl (Sig (SCCSig ...)))` or to > keep shifting to parse an expression. As shifting is the default behavior when a > shift/reduce conflict happens, it's always trying to parse an expression, which > is always the wrong thing to do. > > Does anyone have any ideas on how to handle this? > > Motivation: Not having SCCs at the top level is becoming annoying real quick. > For simplest cases, it's possible to do this transformation: > > f x y = ... > => > f = {-# SCC f #-} \x y -> ... > > However, it doesn't work when there's a `where` clause: > > f x y = > where t = ... > => > f = {-# SCC f #-} \x y -> > where t = ... > > Or when we have a "equation style" definition: > > f (C1 ...) = ... > f (C2 ...) = ... > f (C3 ...) = ... > ... > > (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`) > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From omeragacan at gmail.com Wed Jun 1 12:55:54 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Wed, 1 Jun 2016 08:55:54 -0400 Subject: Parser changes for supporting top-level SCC annotations In-Reply-To: <82C83F49-4D45-4118-B0AC-5C687F931206@cis.upenn.edu> References: <82C83F49-4D45-4118-B0AC-5C687F931206@cis.upenn.edu> Message-ID: I was actually trying to avoid that, thinking that it'd be best if SCC uniformly worked for top-levels and expressions. But then this new form: {-# SCC f "f_scc" #-} Would only work for toplevel SCCs.. So maybe it's OK to introduce a new pragma here. 2016-06-01 8:13 GMT-04:00 Richard Eisenberg : > What about just using a new pragma? > >> {-# SCC_FUNCTION f "f_scc" #-} >> f True = ... >> f False = ... > > The pragma takes the name of the function (a single identifier) and the name of the SCC. If you wish both to have the same name, you can leave off the SCC name. > > It seems worth it to me to introduce a new pragma here. > > Richard > > On May 30, 2016, at 3:14 PM, ?mer Sinan A?acan wrote: > >> I'm trying to support SCCs at the top-level. The implementation should be >> trivial except the parsing part turned out to be tricky. Since expressions can >> appear at the top-level, after a {-# SCC ... #-} parser can't decide whether to >> reduce the token in `sigdecl` to generate a `(LHsDecl (Sig (SCCSig ...)))` or to >> keep shifting to parse an expression. As shifting is the default behavior when a >> shift/reduce conflict happens, it's always trying to parse an expression, which >> is always the wrong thing to do. >> >> Does anyone have any ideas on how to handle this? >> >> Motivation: Not having SCCs at the top level is becoming annoying real quick. >> For simplest cases, it's possible to do this transformation: >> >> f x y = ... >> => >> f = {-# SCC f #-} \x y -> ... >> >> However, it doesn't work when there's a `where` clause: >> >> f x y = >> where t = ... >> => >> f = {-# SCC f #-} \x y -> >> where t = ... >> >> Or when we have a "equation style" definition: >> >> f (C1 ...) = ... >> f (C2 ...) = ... >> f (C3 ...) = ... >> ... >> >> (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`) >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From simonpj at microsoft.com Wed Jun 1 14:55:56 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 1 Jun 2016 14:55:56 +0000 Subject: Deriving Generic1 Message-ID: <659ae7fff77b4137a55ff35a933598ce@DB4PR30MB030.064d.mgd.msft.net> Ryan If you compile newtype Compose f g a = Compose (f (g a)) deriving( Generic1 ) and do ?show-iface on the resulting hi file, you?ll see $fGeneric1Compose :: forall (f :: * -> *) k (g :: k -> *). Functor f => Generic1 (Compose f g) I was expecting to see $fGeneric1Compose :: forall (f :: k1 -> *) k (g :: k -> k1). (..something..) => Generic1 (Compose f g) Otherwise the Generic1 instance only works if its first argument has kind (* -> *). Is that the intention? Maybe so? Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Wed Jun 1 15:09:37 2016 From: spam at scientician.net (Bardur Arantsson) Date: Wed, 1 Jun 2016 17:09:37 +0200 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: On 06/01/2016 01:48 PM, Akio Takano wrote: > Hi, > > Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would > love to see in GHC. It's a small syntactic extension that allows do, > case, if and lambda blocks as function arguments, without parentheses. > However, its differential revision [1] has been abandoned, citing a > mixed response from the community. A message [2] on the ticket > summarizes a thread in haskell-cafe on this topic. > > I, for one, think adding this extension is worthwhile, because a > significant number of people support it. Also, given how some people > seem to feel ambivalent about this change, I believe actually allowing > people to try it makes it clearer whether it is a good idea. > > Thus I'm wondering: is there any chance that this gets merged? If so, > I'm willing to work on whatever is remaining to get the change merged. > What's changed since it was last discussed? I don't think the objections were centered in the implementation, so I don't see what "whatever is remaining to get the change merged" would be. AFAICT at best it's a *very* small improvement[1] and fractures Haskell syntax even more around extensions -- tooling etc. will need to understand even *more* syntax extensions[2]. Regards, [1] If you grant that it is indeed an improvment, which I, personally, don't think it is. [2] I think most people agree that this is something that should perhaps be handled by something like https://github.com/haskell/haskell-ide-engine so that it would only need to be implemented once, but there's not even an alpha release yet, so that particular objection stands, AFAICT. From ryan.gl.scott at gmail.com Wed Jun 1 15:21:55 2016 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 1 Jun 2016 11:21:55 -0400 Subject: Deriving Generic1 In-Reply-To: <659ae7fff77b4137a55ff35a933598ce@DB4PR30MB030.064d.mgd.msft.net> References: <659ae7fff77b4137a55ff35a933598ce@DB4PR30MB030.064d.mgd.msft.net> Message-ID: This is a consequence of the way GHC generics represents datatypes that compose functor-like types in this fashion. If you compile that code with -ddump-deriv, you'll see that the Rep1 for Compose is (in abbreviated form): type Rep1 (Compose f g) = ... (f :.: Rec1 g) where (:.:) is defined as [1]: newtype (:.:) (f :: k2 -> *) (g :: k1 -> k2) (p :: k1) = Comp1 (f (g p)) In other words, we must kind-check the type (f (Rec1 g p)). But Rec1 is a datatype, so it must have result kind *. Therefore, the kind of f is forced to be (* -> *). I describe this in a Note here [2]. This feels like a somewhat fundamental consequence of using datatypes to abstract over a datatype's structure, so I'm not aware of a way around this. Luckily, the kind of g is still (k -> *), which was the main goal of Trac #10604 [3]. Ryan S. ----- [1] http://git.haskell.org/ghc.git/blob/0676e68cf5fe8696f1f760fef0f35dba14db1104:/libraries/base/GHC/Generics.hs#l865 [2] http://git.haskell.org/ghc.git/blob/0676e68cf5fe8696f1f760fef0f35dba14db1104:/compiler/typecheck/TcGenGenerics.hs#l907 [3] https://ghc.haskell.org/trac/ghc/ticket/10604 On Wed, Jun 1, 2016 at 10:55 AM, Simon Peyton Jones wrote: > Ryan > > If you compile > > newtype Compose f g a = Compose (f (g a)) deriving( Generic1 ) > > and do ?show-iface on the resulting hi file, you?ll see > > $fGeneric1Compose :: > > forall (f :: * -> *) k (g :: k -> *). > > Functor f => > > Generic1 (Compose f g) > > I was expecting to see > > $fGeneric1Compose :: > > forall (f :: k1 -> *) k (g :: k -> k1). > > (..something..) => > > Generic1 (Compose f g) > > Otherwise the Generic1 instance only works if its first argument has kind (* > -> *). > > Is that the intention? Maybe so? > > Simon From ekmett at gmail.com Wed Jun 1 16:32:46 2016 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 1 Jun 2016 12:32:46 -0400 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: Just as a note: I noticed this was being discussed a couple of weeks ago as a possible topic for haskell-prime, when they were discussing what was in scope for the committee, so I'm not entirely sure its a dead topic. -Edward On Wed, Jun 1, 2016 at 11:09 AM, Bardur Arantsson wrote: > On 06/01/2016 01:48 PM, Akio Takano wrote: > > Hi, > > > > Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would > > love to see in GHC. It's a small syntactic extension that allows do, > > case, if and lambda blocks as function arguments, without parentheses. > > However, its differential revision [1] has been abandoned, citing a > > mixed response from the community. A message [2] on the ticket > > summarizes a thread in haskell-cafe on this topic. > > > > I, for one, think adding this extension is worthwhile, because a > > significant number of people support it. Also, given how some people > > seem to feel ambivalent about this change, I believe actually allowing > > people to try it makes it clearer whether it is a good idea. > > > > Thus I'm wondering: is there any chance that this gets merged? If so, > > I'm willing to work on whatever is remaining to get the change merged. > > > > What's changed since it was last discussed? I don't think the objections > were centered in the implementation, so I don't see what "whatever is > remaining to get the change merged" would be. > > AFAICT at best it's a *very* small improvement[1] and fractures Haskell > syntax even more around extensions -- tooling etc. will need to > understand even *more* syntax extensions[2]. > > Regards, > > [1] If you grant that it is indeed an improvment, which I, personally, > don't think it is. > > [2] I think most people agree that this is something that should perhaps > be handled by something like > https://github.com/haskell/haskell-ide-engine so that it would only need > to be implemented once, but there's not even an alpha release yet, so > that particular objection stands, AFAICT. > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From baldurpet at gmail.com Wed Jun 1 17:01:54 2016 From: baldurpet at gmail.com (=?UTF-8?Q?Baldur_Bl=C3=B6ndal?=) Date: Wed, 1 Jun 2016 17:01:54 +0000 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: This gets a guilty +1 from me, I have always found $ busy and cumbersome to read. Patterns such as ?f a b c $ do? are ubiquitous (especially in ESDLs where clean syntax matters more) and code such as > dataFetch req = Fetch $ \ref -> do awkwardly requires 3 steps ($, lambda, do). 2016-06-01 16:32 GMT, Edward Kmett : > Just as a note: I noticed this was being discussed a couple of weeks ago as > a possible topic for haskell-prime, when they were discussing what was in > scope for the committee, so I'm not entirely sure its a dead topic. > > -Edward > > On Wed, Jun 1, 2016 at 11:09 AM, Bardur Arantsson > wrote: > >> On 06/01/2016 01:48 PM, Akio Takano wrote: >> > Hi, >> > >> > Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would >> > love to see in GHC. It's a small syntactic extension that allows do, >> > case, if and lambda blocks as function arguments, without parentheses. >> > However, its differential revision [1] has been abandoned, citing a >> > mixed response from the community. A message [2] on the ticket >> > summarizes a thread in haskell-cafe on this topic. >> > >> > I, for one, think adding this extension is worthwhile, because a >> > significant number of people support it. Also, given how some people >> > seem to feel ambivalent about this change, I believe actually allowing >> > people to try it makes it clearer whether it is a good idea. >> > >> > Thus I'm wondering: is there any chance that this gets merged? If so, >> > I'm willing to work on whatever is remaining to get the change merged. >> > >> >> What's changed since it was last discussed? I don't think the objections >> were centered in the implementation, so I don't see what "whatever is >> remaining to get the change merged" would be. >> >> AFAICT at best it's a *very* small improvement[1] and fractures Haskell >> syntax even more around extensions -- tooling etc. will need to >> understand even *more* syntax extensions[2]. >> >> Regards, >> >> [1] If you grant that it is indeed an improvment, which I, personally, >> don't think it is. >> >> [2] I think most people agree that this is something that should perhaps >> be handled by something like >> https://github.com/haskell/haskell-ide-engine so that it would only need >> to be implemented once, but there's not even an alpha release yet, so >> that particular objection stands, AFAICT. >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > From tkn.akio at gmail.com Wed Jun 1 22:26:27 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Thu, 2 Jun 2016 07:26:27 +0900 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: Hi Bardur, On 2 June 2016 at 00:09, Bardur Arantsson wrote: > On 06/01/2016 01:48 PM, Akio Takano wrote: >> Hi, >> >> Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would >> love to see in GHC. It's a small syntactic extension that allows do, >> case, if and lambda blocks as function arguments, without parentheses. >> However, its differential revision [1] has been abandoned, citing a >> mixed response from the community. A message [2] on the ticket >> summarizes a thread in haskell-cafe on this topic. >> >> I, for one, think adding this extension is worthwhile, because a >> significant number of people support it. Also, given how some people >> seem to feel ambivalent about this change, I believe actually allowing >> people to try it makes it clearer whether it is a good idea. >> >> Thus I'm wondering: is there any chance that this gets merged? If so, >> I'm willing to work on whatever is remaining to get the change merged. >> > > What's changed since it was last discussed? Nothing has really changed. I'm just trying to argue that the current level of community support is good enough to justify an implementation. Please note that the previous Differential revision was abandoned by the author. It was *not* rejected due to a lack of support. Hence my question: if properly implemented, does this feature have any chance of getting merged in, or is it regarded too controversial? > I don't think the objections > were centered in the implementation, so I don't see what "whatever is > remaining to get the change merged" would be. I'm referring the points mentioned in the review comments in the Differential revision. For example this change needs an update to the User's Guide. > > AFAICT at best it's a *very* small improvement[1] and fractures Haskell > syntax even more around extensions -- tooling etc. will need to > understand even *more* syntax extensions[2]. I disagree that this is a small improvement, but I don't intend to debate this here. As you said, nothing has really changed since it was discussed before, and a lot of reasons for implementing this extension have been already pointed out. I don't have anything to add. Regarding tooling, my understanding is that most tools that need to understand Haskell (this includes ghc-mod and hdevtools) use either the GHC API or haskell-src-exts, so I don't think this extension would need changes in many places. Regards, Takano Akio > > Regards, > > [1] If you grant that it is indeed an improvment, which I, personally, > don't think it is. > > [2] I think most people agree that this is something that should perhaps > be handled by something like > https://github.com/haskell/haskell-ide-engine so that it would only need > to be implemented once, but there's not even an alpha release yet, so > that particular objection stands, AFAICT. > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From john_ericson at brown.edu Thu Jun 2 00:37:54 2016 From: john_ericson at brown.edu (Ericson, John) Date: Wed, 1 Jun 2016 17:37:54 -0700 Subject: Break Base Faster Message-ID: I'm excited for the various proposals to clean up base's warts, but the time-frames over which to distribute the breaking changes are just so long---approaching a decade IIUC for Monad-Fail for example. First off, If anybody has some links to where/why the long transitions were proposed, I'd love to read them as I am not sure of the exact motivation. If, in fact, we could just break everything all at once without pissing people off, then the rest of my email can be discarded :). As I see it, the underlying issue here is that we are assuming each GHC version will only work with one version of base. Well, as it stands, none of the proposed *breaking* changes interact much with the language itself, so the relationship between base and GHC is less constrained than it seems. I went on #ghc and learned that multiple bases was tried in the past for Haskell98 compatability and exceptions in 6.10, and the experience was unpleasant. But I hope that Cabal support for multiple versions of a package in a single build plan ( http://www.well-typed.com/blog/2015/07/cabal-setup-deps/), Stackage package sets, and split base can improve the experience this time around. Cabal improvements perhaps open the door to linking packages that use different base versions together, with blanket instances from e.g. (new.Monad, new.MonadFail) => old.Monad to ease the pain. With package-qualified-imports, I hope we can have legacy base import from base, but otherwise we can make them both rely on other packages (especially with split-base), from which base will just re-export definitions. In the event that linking both bases is impossible, or the blanket instances are insufficient for making the same library work with other libraries requiring either base. Stackage will allow for curating separate package sets for each base version. I imagine the prospect of splitting the Haskell ecosystem with multiple bases sounds daunting to some, but package sets like Stackage provides provide enough cohesion *within* the ecosystem centered around each base that I'd wager we'd still be in better shape than how things were circa 6.10. Finally, split base I hope will generally make experimentation easier by allowing packages to specify more exactly what they need, and lower the barrier of entry for new bases. As mentioned above, it allow for legacy base to more more naturally contain blanket instances of normal base's classes by avoiding package-qualified imports. For the first release with split base, I'd follow Rust's example where base is a "facade" and the packages that back it are initially unstable like ghc-prim. According to https://ghc.haskell.org/trac/ghc/wiki/SplitBase#Non-Obviousinterdependencies, the completion of MonadFail is in fact a big prerequisite to an acyclic split base. If my previous statements are correct on the benefits of split base, this puts us in an pleasant situation where MonadFail can speed up split base, and split base can speed up Monad fail. As a final thought, I think that multiple bases is far superior than taking the "-compat" route a la transformers-compat: IMO the need to change upstream code to use "-compat" severely negates the benefits. John -------------- next part -------------- An HTML attachment was scrubbed... URL: From mgsloan at gmail.com Thu Jun 2 01:07:10 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 1 Jun 2016 18:07:10 -0700 Subject: Template Haskell determinism In-Reply-To: References: Message-ID: +1 to solving this. Not sure about the approach, but assuming the following concerns are addressed, I'm (+1) on it too: This solution is clever! However, I think there is some difficulty to determining this ordering key. Namely, what happens when I construct the (Set Name) using results from multiple reifies? One solution is to have the ordering key be a consecutive supply that's initialized on a per-module basis. There is still an issue there, though, which is that you might store one of these names in a global IORef that's used by a later TH splice. Or, similarly, serialize the names to a file and later load them. At least in those cases you need to use 'runIO' to break determinism. If names get different ordering keys when reified from different modules (seems like they'd have to, particularly given ghc's "-j"), then we end up with an unpleasant circumstance where these do not compare as equal. How about having the Eq instance ignore the ordering key? I think that mostly resolves this concern. This implies that the Ord instance should also yield EQ and ignore the ordering key, when the unique key matches. One issue with this is that switching the order of reify could unexpectedly vary the behavior. Does the map in TcGblEnv imply that a reify from a later module will get the same ordering key? So does this mean that the keys used in a given reify depend on which things have already been reified? In that case, then this is also an issue with your solution. Now, it's not a big problem at all, just surprising to the user. If the internal API for Name does change, may as well address https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's suggested solution of having both the traditional package identifier and package keys in 'Name'. -Michael On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka wrote: > Template Haskell with its ability to do arbitrary IO is non-deterministic > by > design. You could for example embed the current date in a file. There is > however one kind of non-deterministic behavior that you can trigger > accidentally. It has to do with how Names are reified. If you take a look > at > the definition of reifyName you can see that it puts the assigned Unique > in a > NameU: > > reifyName :: NamedThing n => n -> TH.Name > reifyName thing > | isExternalName name = mk_varg pkg_str mod_str occ_str > | otherwise = TH.mkNameU occ_str (getKey (getUnique name)) > ... > NameFlavour which NameU is a constructor of has a default Ord instance, > meaning > that it ends up comparing the Uniques. The relative ordering of Uniques is > not > guaranteed to be stable across recompilations [1], so this can lead to > ABI-incompatible binaries. > > This isn't an abstract problem and it actually happens in practice. The > microlens package keeps Names in a Set and later turns that set into a > list. > The results have different orders of TyVars resulting in different ABI > hashes > and can potentially be optimized differently. > > I believe it's worth to handle this case in a deterministic way and I have > a > solution in mind. The idea is to extend NameU (and potentially NameL) with > an > ordering key. To be more concrete: > > - | NameU !Int > + | NameU !Int !Int > > This way the Ord instance can use a stable key and the problem reduces to > ensuring the keys are stable. To generate stable keys we can use the fact > that > reify traverses the expressions in the same order every time and > sequentially > allocate new keys based on traversal order. The way I have it implemented > now > is to add a new field in TcGblEnv which maps Uniques to allocated keys: > > + tcg_th_names :: TcRef (UniqFM Int, Int), > > Then the reifyName and qNewName do the necessary bookkeeping and translate > the > Uniques on the fly. > > This is a breaking change and it doesn't fix the problem that NameFlavour > is > not abstract and leaks the Uniques. It would break at least: > > - singletons > - th-lift > - haskell-src-meta > - shakespeare > - distributed-closure > > I'd like to get feedback if this is an acceptable solution and if the > problem > is worth solving. > > Cheers, > Bartosz > > [1] > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 2 07:19:50 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 2 Jun 2016 07:19:50 +0000 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: Akio Thanks for bringing back the ArgumentsDo question. My personal take on it is similar to Bardur: > AFAICT at best it's a *very* small improvement[1] and fractures > Haskell syntax even more around extensions -- tooling etc. will need > to understand even *more* syntax extensions[2]. The benefit to me seems slight. The cost is also modest, but it is not zero (see below), even given a complete implementation. ANY feature carries a cost that is borne by every subsequent implementor, in perpetuity. So I am a bit reluctant. These things are a judgement call, and we don't have a good process for making that decision. A few of us have been talking about putting forward a better process; it'll be a few weeks. Meanwhile, what to do about ArgumentDo? You say | I disagree that this is a small improvement, but I don't intend to | debate this here. As you said, nothing has really changed since it was | discussed before, and a lot of reasons for implementing this extension | have been already pointed out. I don't have anything to add. Is there a wiki page that describes the proposal, and lists the "lot of reasons" why it would be a good thing? And lists any disadvantages? I'm not just erecting obstacles: the trouble with email is that it is long and discursive, so it's really hard to find all the relevant messages, and even if you do each message only makes sense if you read the long sequence. One question I have is this. Presumably f do stmts will be represented as HsApp (HsVar f) (HsDo ...stmts...) And should print without parens -- they are signalled by HsPar. So what about (HsApp (HsVar f) (HsDo ...stmts1..)) (HsDo ..stmts2..) How does that pretty-print. I suppose it should be f do stmts1 do stmts2 That is, it must use layout. But at the moment the pretty printer doesn't do that. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Akio | Takano | Sent: 01 June 2016 23:26 | To: Bardur Arantsson | Cc: ghc-devs | Subject: Re: Moving ArgumentsDo forward | | Hi Bardur, | | On 2 June 2016 at 00:09, Bardur Arantsson | wrote: | > On 06/01/2016 01:48 PM, Akio Takano wrote: | >> Hi, | >> | >> Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would | >> love to see in GHC. It's a small syntactic extension that allows | do, | >> case, if and lambda blocks as function arguments, without | parentheses. | >> However, its differential revision [1] has been abandoned, citing a | >> mixed response from the community. A message [2] on the ticket | >> summarizes a thread in haskell-cafe on this topic. | >> | >> I, for one, think adding this extension is worthwhile, because a | >> significant number of people support it. Also, given how some | people | >> seem to feel ambivalent about this change, I believe actually | >> allowing people to try it makes it clearer whether it is a good | idea. | >> | >> Thus I'm wondering: is there any chance that this gets merged? If | so, | >> I'm willing to work on whatever is remaining to get the change | merged. | >> | > | > What's changed since it was last discussed? | | Nothing has really changed. I'm just trying to argue that the current | level of community support is good enough to justify an | implementation. | | Please note that the previous Differential revision was abandoned by | the author. It was *not* rejected due to a lack of support. Hence my | question: if properly implemented, does this feature have any chance | of getting merged in, or is it regarded too controversial? | | > I don't think the objections | > were centered in the implementation, so I don't see what "whatever | is | > remaining to get the change merged" would be. | | I'm referring the points mentioned in the review comments in the | Differential revision. For example this change needs an update to the | User's Guide. | | > | > AFAICT at best it's a *very* small improvement[1] and fractures | > Haskell syntax even more around extensions -- tooling etc. will need | > to understand even *more* syntax extensions[2]. | | I disagree that this is a small improvement, but I don't intend to | debate this here. As you said, nothing has really changed since it was | discussed before, and a lot of reasons for implementing this extension | have been already pointed out. I don't have anything to add. | | Regarding tooling, my understanding is that most tools that need to | understand Haskell (this includes ghc-mod and hdevtools) use either | the GHC API or haskell-src-exts, so I don't think this extension would | need changes in many places. | | Regards, | Takano Akio | | > | > Regards, | > | > [1] If you grant that it is indeed an improvment, which I, | personally, | > don't think it is. | > | > [2] I think most people agree that this is something that should | > perhaps be handled by something like | > https://github.com/haskell/haskell-ide-engine so that it would only | > need to be implemented once, but there's not even an alpha release | > yet, so that particular objection stands, AFAICT. | > | > | > _______________________________________________ | > ghc-devs mailing list | > ghc-devs at haskell.org | > | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | > askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7csi | > | monpj%40064d.mgd.microsoft.com%7c738d83b44c5c4a806d4208d38a6bd2fe%7c72 | > | f988bf86f141af91ab2d7cd011db47%7c1&sdata=9gGIMGGJZgWFHueOeKUyIAzUaZuun | > %2b3PwKEzctMizss%3d | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c738d83b44c5c4a8 | 06d4208d38a6bd2fe%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=9gGIMGG | JZgWFHueOeKUyIAzUaZuun%2b3PwKEzctMizss%3d From simonpj at microsoft.com Thu Jun 2 07:32:56 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 2 Jun 2016 07:32:56 +0000 Subject: Break Base Faster In-Reply-To: References: Message-ID: John ? with notes for Edward K (core libraries) I'm excited for the various proposals to clean up base's warts, but the time-frames over which to distribute the breaking changes are just so long You should really address this to the Core Libraries Committee, not ghc-devs A huge motivation for slow change in base is to avoid breaking libraries. In fact the core libraries committee settled on a ?Three release policy?. It?s described here but that page says ?not finalised? and it is not linked from the Core Libraries Committee page. I?m all for splitting base up. Lots of base is NOT connected with the compiler, and moving that out would be good. As it happens, Monad *is* connected; e.g. via do-notation. And MonadFail is connected with how pattern matching in do-notation works. So I rather doubt you could change Monad around without also changing GHC in sync. That?s why base and GHC are the same repo. But yes ? please shrink it! Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ericson, John Sent: 02 June 2016 01:38 To: ghc-devs Subject: Break Base Faster I'm excited for the various proposals to clean up base's warts, but the time-frames over which to distribute the breaking changes are just so long---approaching a decade IIUC for Monad-Fail for example. First off, If anybody has some links to where/why the long transitions were proposed, I'd love to read them as I am not sure of the exact motivation. If, in fact, we could just break everything all at once without pissing people off, then the rest of my email can be discarded :). As I see it, the underlying issue here is that we are assuming each GHC version will only work with one version of base. Well, as it stands, none of the proposed breaking changes interact much with the language itself, so the relationship between base and GHC is less constrained than it seems. I went on #ghc and learned that multiple bases was tried in the past for Haskell98 compatability and exceptions in 6.10, and the experience was unpleasant. But I hope that Cabal support for multiple versions of a package in a single build plan (http://www.well-typed.com/blog/2015/07/cabal-setup-deps/), Stackage package sets, and split base can improve the experience this time around. Cabal improvements perhaps open the door to linking packages that use different base versions together, with blanket instances from e.g. (new.Monad, new.MonadFail) => old.Monad to ease the pain. With package-qualified-imports, I hope we can have legacy base import from base, but otherwise we can make them both rely on other packages (especially with split-base), from which base will just re-export definitions. In the event that linking both bases is impossible, or the blanket instances are insufficient for making the same library work with other libraries requiring either base. Stackage will allow for curating separate package sets for each base version. I imagine the prospect of splitting the Haskell ecosystem with multiple bases sounds daunting to some, but package sets like Stackage provides provide enough cohesion within the ecosystem centered around each base that I'd wager we'd still be in better shape than how things were circa 6.10. Finally, split base I hope will generally make experimentation easier by allowing packages to specify more exactly what they need, and lower the barrier of entry for new bases. As mentioned above, it allow for legacy base to more more naturally contain blanket instances of normal base's classes by avoiding package-qualified imports. For the first release with split base, I'd follow Rust's example where base is a "facade" and the packages that back it are initially unstable like ghc-prim. According to https://ghc.haskell.org/trac/ghc/wiki/SplitBase#Non-Obviousinterdependencies, the completion of MonadFail is in fact a big prerequisite to an acyclic split base. If my previous statements are correct on the benefits of split base, this puts us in an pleasant situation where MonadFail can speed up split base, and split base can speed up Monad fail. As a final thought, I think that multiple bases is far superior than taking the "-compat" route a la transformers-compat: IMO the need to change upstream code to use "-compat" severely negates the benefits. John -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 2 11:12:13 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 2 Jun 2016 11:12:13 +0000 Subject: Template Haskell determinism In-Reply-To: References: Message-ID: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> If names get different ordering keys when reified from different modules (seems like they'd have to, particularly given ghc's "-j"), then we end up with an unpleasant circumstance where these do not compare as equal The I believe that global, top level names (NameG) are not subject to this ordering stuff, so I don?t think this problem can occur. This is a breaking change and it doesn't fix the problem that NameFlavour is not abstract and leaks the Uniques. It would break at least: But why is NameU exposed to clients? GHC needs to know, but clients don?t. What use are these packages making of it? S From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Michael Sloan Sent: 02 June 2016 02:07 To: Bartosz Nitka Cc: ghc-devs Devs Subject: Re: Template Haskell determinism +1 to solving this. Not sure about the approach, but assuming the following concerns are addressed, I'm (+1) on it too: This solution is clever! However, I think there is some difficulty to determining this ordering key. Namely, what happens when I construct the (Set Name) using results from multiple reifies? One solution is to have the ordering key be a consecutive supply that's initialized on a per-module basis. There is still an issue there, though, which is that you might store one of these names in a global IORef that's used by a later TH splice. Or, similarly, serialize the names to a file and later load them. At least in those cases you need to use 'runIO' to break determinism. If names get different ordering keys when reified from different modules (seems like they'd have to, particularly given ghc's "-j"), then we end up with an unpleasant circumstance where these do not compare as equal. How about having the Eq instance ignore the ordering key? I think that mostly resolves this concern. This implies that the Ord instance should also yield EQ and ignore the ordering key, when the unique key matches. One issue with this is that switching the order of reify could unexpectedly vary the behavior. Does the map in TcGblEnv imply that a reify from a later module will get the same ordering key? So does this mean that the keys used in a given reify depend on which things have already been reified? In that case, then this is also an issue with your solution. Now, it's not a big problem at all, just surprising to the user. If the internal API for Name does change, may as well address https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's suggested solution of having both the traditional package identifier and package keys in 'Name'. -Michael On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka > wrote: Template Haskell with its ability to do arbitrary IO is non-deterministic by design. You could for example embed the current date in a file. There is however one kind of non-deterministic behavior that you can trigger accidentally. It has to do with how Names are reified. If you take a look at the definition of reifyName you can see that it puts the assigned Unique in a NameU: reifyName :: NamedThing n => n -> TH.Name reifyName thing | isExternalName name = mk_varg pkg_str mod_str occ_str | otherwise = TH.mkNameU occ_str (getKey (getUnique name)) ... NameFlavour which NameU is a constructor of has a default Ord instance, meaning that it ends up comparing the Uniques. The relative ordering of Uniques is not guaranteed to be stable across recompilations [1], so this can lead to ABI-incompatible binaries. This isn't an abstract problem and it actually happens in practice. The microlens package keeps Names in a Set and later turns that set into a list. The results have different orders of TyVars resulting in different ABI hashes and can potentially be optimized differently. I believe it's worth to handle this case in a deterministic way and I have a solution in mind. The idea is to extend NameU (and potentially NameL) with an ordering key. To be more concrete: - | NameU !Int + | NameU !Int !Int This way the Ord instance can use a stable key and the problem reduces to ensuring the keys are stable. To generate stable keys we can use the fact that reify traverses the expressions in the same order every time and sequentially allocate new keys based on traversal order. The way I have it implemented now is to add a new field in TcGblEnv which maps Uniques to allocated keys: + tcg_th_names :: TcRef (UniqFM Int, Int), Then the reifyName and qNewName do the necessary bookkeeping and translate the Uniques on the fly. This is a breaking change and it doesn't fix the problem that NameFlavour is not abstract and leaks the Uniques. It would break at least: - singletons - th-lift - haskell-src-meta - shakespeare - distributed-closure I'd like to get feedback if this is an acceptable solution and if the problem is worth solving. Cheers, Bartosz [1] https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Fri Jun 3 02:09:34 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Thu, 2 Jun 2016 22:09:34 -0400 Subject: Template Haskell determinism In-Reply-To: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <47772C60-C928-41A8-9DFC-2AB581B21F6A@cis.upenn.edu> On Jun 2, 2016, at 7:12 AM, Simon Peyton Jones wrote: > > But why is NameU exposed to clients? GHC needs to know, but clients don?t. What use are these packages making of it? > singletons uses NameU in two places: 1. To generate unique numbers. It would be easy enough for me to put this functionality in my own monad, though. 2. More importantly, to work around GHC's #11812, caused by the fact that `NameU`s don't always work when other Names would. So I have to squeeze out `NameU`s in one spot. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicola.gigante at gmail.com Fri Jun 3 15:25:15 2016 From: nicola.gigante at gmail.com (Nicola Gigante) Date: Fri, 3 Jun 2016 17:25:15 +0200 Subject: Why does the LLVM invoke command-line tools instead of using the library? Message-ID: Hi all, while looking at the GHC 8 Trac page I encountered the page about the plans for the improved LLVM backend: https://ghc.haskell.org/trac/ghc/wiki/ImprovedLLVMBackend I know nearly nothing about the internals of the GHC backend so I may be asking something trivial, but from reading that page I understand that GHC currently calls LLVM command line tools to optimize and compile the IR, is it right? LLVM is a C++ library, but it also exports a portable and stable C API which I think is already covered by the llvm-general package. So as someone who worked on LLVM in the past, and appreciated its library-based integration-friendly design I?m wondering why is GHC using the command line tools instead of linking to the library? Best Regards, Nicola -------------- next part -------------- An HTML attachment was scrubbed... URL: From pi.boy.travis at gmail.com Sat Jun 4 05:48:16 2016 From: pi.boy.travis at gmail.com (Travis Whitaker) Date: Sat, 4 Jun 2016 01:48:16 -0400 Subject: Linux (ELF) Support for "ghc -static -shared" Message-ID: Suppose I have some module Foo with foreign exports. On some platforms I can do something like: ghc -static -shared Foo.o ... The resulting shared library would have the base libraries and the RTS statically linked in. From what I understand this is possible on BSDs because generating PIC is the default there (for making PIEs I'd imagine), and possible on Windows because the dynamic loading process involves some technique that doesn't require PIC. On Linux (at least x86_64) this doesn't work by default since libHSbase, libHSrts et al. are not built with -fPIC unless one specifically asks for it when building GHC. As far as I know this is the only way to get -static -shared to work on this platform. While the use cases for such stand-alone shared libraries might be small niches, I was curious whether or not there was any discussion about potential strategies for making it easier to build them for Linux. At the very least, perhaps a single switch for the configure script or build.mk to make it easier to build GHC+libs with -fPIC on Linux. Another step up might be providing *_PIC.a objects for the base libraries, so that the non-PIC objects are still available for the majority of cases in which PIC is not required. Thanks for your time, Travis Whitaker -------------- next part -------------- An HTML attachment was scrubbed... URL: From minesasecret at gmail.com Sat Jun 4 17:10:42 2016 From: minesasecret at gmail.com (Richard Fung) Date: Sat, 4 Jun 2016 10:10:42 -0700 Subject: Help on first ticket Message-ID: Hello! I apologize if this isn't the right place to ask; if it isn't please steer me in the right direction. Would anyone be willing to advise me on my first ticket? I've been trying to work on it on and off but haven't made much progress on my own. It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 I think I understand the issue conceptually but I don't know where to look for the code that needs to be changed.. Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Sat Jun 4 22:20:07 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Sun, 05 Jun 2016 00:20:07 +0200 Subject: Help on first ticket In-Reply-To: References: Message-ID: <87vb1ok354.fsf@smart-cactus.org> Richard Fung writes: > Hello! I apologize if this isn't the right place to ask; if it isn't please > steer me in the right direction. > Hi Richard! > Would anyone be willing to advise me on my first ticket? I've been trying > to work on it on and off but haven't made much progress on my own. > > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 > Great, I'm happy to hear that someone has picked this one up. I think it is a nice choice for a self-contained newcomers project. > I think I understand the issue conceptually but I don't know where to look > for the code that needs to be changed.. > I don't know where the code responsible for this is off the top of my head, however I can provide some pointers. So the unfoldings you are looking to preserve come from interface files. The machinery for all of this is in compiler/iface. IfaceSyn.hs is of particular interest and there you will find the definition of IfaceUnfolding, which is the unfolding representation which is stored in the interface file. Unfoldings live inside of IdInfo values, which hold various miscellaneous information which we need to preserve about a particular Id (identifier). There is a somewhat useful comment regarding how IdInfo is treated above the definition of IfaceIdInfo in IfaceSyn. In particular it seems that interface files for modules compiled with -O0 will have their IdInfo fields set to NoInfo. It's not clear what happens when an interface file is read. However, grepping for NoInfo reveals a use-site in TcIface.tcIdInfo which looks interesting (in particular the ignore_prags guard). I think this should be enough to get you going on the interface file part of this. The other part of this ticket is deciding whether to use an unfolding when considering whether to inline. This will be done in the simplifier (compiler/simplCore). Grepping for "inline" and "unfold" in simplCore/Simplify.hs (as well as reading the notes in that file) will likely be enough to get you started. Do let me know if you still feel lost or want to discuss this further. I look forward to hearing how it goes. Cheers, - Ben From mgsloan at gmail.com Sun Jun 5 01:44:03 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Sat, 4 Jun 2016 18:44:03 -0700 Subject: Template Haskell determinism In-Reply-To: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> Message-ID: On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones wrote: > If names get different ordering keys when reified from different modules > (seems like they'd have to, particularly given ghc's "-j"), then we end up > with an unpleasant circumstance where these do not compare as equal > > > > The I believe that global, top level names (NameG) are not subject to this > ordering stuff, so I don?t think this problem can occur. > True, top level names are NameG. The reified Info for a top level Dec may include NameU, though. For example, the type variables in 'Maybe' are NameU: $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe lift (show nf)) The resulting expression is something like "NameU 822083586" > This is a breaking change and it doesn't fix the problem that NameFlavour > is > > not abstract and leaks the Uniques. It would break at least: > > > > But why is NameU exposed to clients? GHC needs to know, but clients > don?t. What use are these packages making of it? > It's being leaked in the public inteface via Ord. The Eq instance is fine, because these are Uniques, so the results should be consistent. There are two goals in contention here: 1) Having some ordering on Names so that they can be used in Map or Set 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to really handle these well. In that case, the ordering would be based on everything but the NameU int, but 'Eq' would still follow it A few ideas for different approaches to resolving this: 1) Document it. Less appealing than fixing it in the API, but still would be good. 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' newtype (partial ord on the non-unique info), or 'UnstableNameOrd' newtype (current behavior). A trickyness of this approach is that you'd need containers that can handle (PartialOrd k, Eq k) keys. In lots of cases people are using the 'Ord' instance with 'Name's that are not 'NameU', so this would break a lot of code that was already deterministic. 3) Some approaches like this ordering key, but I'm not sure how it will help when comparing NameUs from different modules? > S > > > > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Michael > Sloan > *Sent:* 02 June 2016 02:07 > *To:* Bartosz Nitka > *Cc:* ghc-devs Devs > *Subject:* Re: Template Haskell determinism > > > > +1 to solving this. Not sure about the approach, but assuming the > following concerns are addressed, I'm (+1) on it too: > > > > This solution is clever! However, I think there is some difficulty to > determining this ordering key. Namely, what happens when I construct the > (Set Name) using results from multiple reifies? > > > > One solution is to have the ordering key be a consecutive supply that's > initialized on a per-module basis. There is still an issue there, though, > which is that you might store one of these names in a global IORef that's > used by a later TH splice. Or, similarly, serialize the names to a file > and later load them. At least in those cases you need to use 'runIO' to > break determinism. > > > > If names get different ordering keys when reified from different modules > (seems like they'd have to, particularly given ghc's "-j"), then we end up > with an unpleasant circumstance where these do not compare as equal. How > about having the Eq instance ignore the ordering key? I think that mostly > resolves this concern. This implies that the Ord instance should also > yield EQ and ignore the ordering key, when the unique key matches. > > > > One issue with this is that switching the order of reify could > unexpectedly vary the behavior. > > > > Does the map in TcGblEnv imply that a reify from a later module will get > the same ordering key? So does this mean that the keys used in a given > reify depend on which things have already been reified? In that case, then > this is also an issue with your solution. Now, it's not a big problem at > all, just surprising to the user. > > > > > > If the internal API for Name does change, may as well address > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's > suggested solution of having both the traditional package identifier and > package keys in 'Name'. > > > > -Michael > > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka wrote: > > Template Haskell with its ability to do arbitrary IO is non-deterministic > by > > design. You could for example embed the current date in a file. There is > > however one kind of non-deterministic behavior that you can trigger > > accidentally. It has to do with how Names are reified. If you take a look > at > > the definition of reifyName you can see that it puts the assigned Unique > in a > > NameU: > > > > reifyName :: NamedThing n => n -> TH.Name > > reifyName thing > > | isExternalName name = mk_varg pkg_str mod_str occ_str > > | otherwise = TH.mkNameU occ_str (getKey (getUnique name)) > > ... > > NameFlavour which NameU is a constructor of has a default Ord instance, > meaning > > that it ends up comparing the Uniques. The relative ordering of Uniques is > not > > guaranteed to be stable across recompilations [1], so this can lead to > > ABI-incompatible binaries. > > > > This isn't an abstract problem and it actually happens in practice. The > > microlens package keeps Names in a Set and later turns that set into a > list. > > The results have different orders of TyVars resulting in different ABI > hashes > > and can potentially be optimized differently. > > > > I believe it's worth to handle this case in a deterministic way and I have > a > > solution in mind. The idea is to extend NameU (and potentially NameL) with > an > > ordering key. To be more concrete: > > > > - | NameU !Int > > + | NameU !Int !Int > > > > This way the Ord instance can use a stable key and the problem reduces to > > ensuring the keys are stable. To generate stable keys we can use the fact > that > > reify traverses the expressions in the same order every time and > sequentially > > allocate new keys based on traversal order. The way I have it implemented > now > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: > > > > + tcg_th_names :: TcRef (UniqFM Int, Int), > > > > Then the reifyName and qNewName do the necessary bookkeeping and translate > the > > Uniques on the fly. > > > > This is a breaking change and it doesn't fix the problem that NameFlavour > is > > not abstract and leaks the Uniques. It would break at least: > > > > - singletons > > - th-lift > > - haskell-src-meta > > - shakespeare > > - distributed-closure > > > > I'd like to get feedback if this is an acceptable solution and if the > problem > > is worth solving. > > > > Cheers, > > Bartosz > > > > [1] > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From minesasecret at gmail.com Sun Jun 5 04:54:40 2016 From: minesasecret at gmail.com (Richard Fung) Date: Sat, 4 Jun 2016 21:54:40 -0700 Subject: Help on first ticket In-Reply-To: <87vb1ok354.fsf@smart-cactus.org> References: <87vb1ok354.fsf@smart-cactus.org> Message-ID: Awesome that's definitely very helpful! I'll be sure to ask again if/when I get stuck. Thanks!! On Sat, Jun 4, 2016 at 3:20 PM, Ben Gamari wrote: > Richard Fung writes: > > > Hello! I apologize if this isn't the right place to ask; if it isn't > please > > steer me in the right direction. > > > Hi Richard! > > > Would anyone be willing to advise me on my first ticket? I've been trying > > to work on it on and off but haven't made much progress on my own. > > > > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 > > > Great, I'm happy to hear that someone has picked this one up. I think it > is a nice choice for a self-contained newcomers project. > > > I think I understand the issue conceptually but I don't know where to > look > > for the code that needs to be changed.. > > > I don't know where the code responsible for this is off the top of my > head, however I can provide some pointers. > > So the unfoldings you are looking to preserve come from interface files. > The machinery for all of this is in compiler/iface. IfaceSyn.hs is of > particular interest and there you will find the definition of > IfaceUnfolding, which is the unfolding representation which is stored in > the interface file. Unfoldings live inside of IdInfo values, which hold > various miscellaneous information which we need to preserve about a > particular Id (identifier). > > There is a somewhat useful comment regarding how IdInfo is treated above > the definition of IfaceIdInfo in IfaceSyn. In particular it seems that > interface files for modules compiled with -O0 will have their IdInfo > fields set to NoInfo. It's not clear what happens when an interface file > is read. However, grepping for NoInfo reveals a use-site in > TcIface.tcIdInfo which looks interesting (in particular the ignore_prags > guard). I think this should be enough to get you going on the interface > file part of this. > > The other part of this ticket is deciding whether to use an unfolding > when considering whether to inline. This will be done in the simplifier > (compiler/simplCore). Grepping for "inline" and "unfold" in > simplCore/Simplify.hs (as well as reading the notes in that file) will > likely be enough to get you started. > > Do let me know if you still feel lost or want to discuss this further. I > look forward to hearing how it goes. > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Sun Jun 5 17:15:50 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sun, 05 Jun 2016 10:15:50 -0700 Subject: Template Haskell determinism In-Reply-To: References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <1465146843-sup-5444@sabre> I must admit, I am a bit confused by this discussion. It is true that every Name is associated with a Unique. But you don't need the Unique to equality/ordering tests; the names also contain enough (stable) information for stable comparisons of that sort. So why don't we expose that instead of the Unique? Edward Excerpts from Michael Sloan's message of 2016-06-04 18:44:03 -0700: > On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones > wrote: > > > If names get different ordering keys when reified from different modules > > (seems like they'd have to, particularly given ghc's "-j"), then we end up > > with an unpleasant circumstance where these do not compare as equal > > > > > > > > The I believe that global, top level names (NameG) are not subject to this > > ordering stuff, so I don?t think this problem can occur. > > > > True, top level names are NameG. The reified Info for a top level Dec may > include NameU, though. For example, the type variables in 'Maybe' are > NameU: > > $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe > lift (show nf)) > > The resulting expression is something like "NameU 822083586" > > > This is a breaking change and it doesn't fix the problem that NameFlavour > > is > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > But why is NameU exposed to clients? GHC needs to know, but clients > > don?t. What use are these packages making of it? > > > > It's being leaked in the public inteface via Ord. The Eq instance is fine, > because these are Uniques, so the results should be consistent. > > There are two goals in contention here: > > 1) Having some ordering on Names so that they can be used in Map or Set > 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to > really handle these well. In that case, the ordering would be based on > everything but the NameU int, but 'Eq' would still follow it > > A few ideas for different approaches to resolving this: > > 1) Document it. Less appealing than fixing it in the API, but still would > be good. > > 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' > newtype (partial ord on the non-unique info), or 'UnstableNameOrd' newtype > (current behavior). A trickyness of this approach is that you'd need > containers that can handle (PartialOrd k, Eq k) keys. In lots of cases > people are using the 'Ord' instance with 'Name's that are not 'NameU', so > this would break a lot of code that was already deterministic. > > 3) Some approaches like this ordering key, but I'm not sure how it will > help when comparing NameUs from different modules? > > > S > > > > > > > > > > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Michael > > Sloan > > *Sent:* 02 June 2016 02:07 > > *To:* Bartosz Nitka > > *Cc:* ghc-devs Devs > > *Subject:* Re: Template Haskell determinism > > > > > > > > +1 to solving this. Not sure about the approach, but assuming the > > following concerns are addressed, I'm (+1) on it too: > > > > > > > > This solution is clever! However, I think there is some difficulty to > > determining this ordering key. Namely, what happens when I construct the > > (Set Name) using results from multiple reifies? > > > > > > > > One solution is to have the ordering key be a consecutive supply that's > > initialized on a per-module basis. There is still an issue there, though, > > which is that you might store one of these names in a global IORef that's > > used by a later TH splice. Or, similarly, serialize the names to a file > > and later load them. At least in those cases you need to use 'runIO' to > > break determinism. > > > > > > > > If names get different ordering keys when reified from different modules > > (seems like they'd have to, particularly given ghc's "-j"), then we end up > > with an unpleasant circumstance where these do not compare as equal. How > > about having the Eq instance ignore the ordering key? I think that mostly > > resolves this concern. This implies that the Ord instance should also > > yield EQ and ignore the ordering key, when the unique key matches. > > > > > > > > One issue with this is that switching the order of reify could > > unexpectedly vary the behavior. > > > > > > > > Does the map in TcGblEnv imply that a reify from a later module will get > > the same ordering key? So does this mean that the keys used in a given > > reify depend on which things have already been reified? In that case, then > > this is also an issue with your solution. Now, it's not a big problem at > > all, just surprising to the user. > > > > > > > > > > > > If the internal API for Name does change, may as well address > > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's > > suggested solution of having both the traditional package identifier and > > package keys in 'Name'. > > > > > > > > -Michael > > > > > > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka wrote: > > > > Template Haskell with its ability to do arbitrary IO is non-deterministic > > by > > > > design. You could for example embed the current date in a file. There is > > > > however one kind of non-deterministic behavior that you can trigger > > > > accidentally. It has to do with how Names are reified. If you take a look > > at > > > > the definition of reifyName you can see that it puts the assigned Unique > > in a > > > > NameU: > > > > > > > > reifyName :: NamedThing n => n -> TH.Name > > > > reifyName thing > > > > | isExternalName name = mk_varg pkg_str mod_str occ_str > > > > | otherwise = TH.mkNameU occ_str (getKey (getUnique name)) > > > > ... > > > > NameFlavour which NameU is a constructor of has a default Ord instance, > > meaning > > > > that it ends up comparing the Uniques. The relative ordering of Uniques is > > not > > > > guaranteed to be stable across recompilations [1], so this can lead to > > > > ABI-incompatible binaries. > > > > > > > > This isn't an abstract problem and it actually happens in practice. The > > > > microlens package keeps Names in a Set and later turns that set into a > > list. > > > > The results have different orders of TyVars resulting in different ABI > > hashes > > > > and can potentially be optimized differently. > > > > > > > > I believe it's worth to handle this case in a deterministic way and I have > > a > > > > solution in mind. The idea is to extend NameU (and potentially NameL) with > > an > > > > ordering key. To be more concrete: > > > > > > > > - | NameU !Int > > > > + | NameU !Int !Int > > > > > > > > This way the Ord instance can use a stable key and the problem reduces to > > > > ensuring the keys are stable. To generate stable keys we can use the fact > > that > > > > reify traverses the expressions in the same order every time and > > sequentially > > > > allocate new keys based on traversal order. The way I have it implemented > > now > > > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: > > > > > > > > + tcg_th_names :: TcRef (UniqFM Int, Int), > > > > > > > > Then the reifyName and qNewName do the necessary bookkeeping and translate > > the > > > > Uniques on the fly. > > > > > > > > This is a breaking change and it doesn't fix the problem that NameFlavour > > is > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > - singletons > > > > - th-lift > > > > - haskell-src-meta > > > > - shakespeare > > > > - distributed-closure > > > > > > > > I'd like to get feedback if this is an acceptable solution and if the > > problem > > > > is worth solving. > > > > > > > > Cheers, > > > > Bartosz > > > > > > > > [1] > > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > > > > > From davidterei at gmail.com Sun Jun 5 17:23:59 2016 From: davidterei at gmail.com (David Terei) Date: Sun, 5 Jun 2016 10:23:59 -0700 Subject: Why does the LLVM invoke command-line tools instead of using the library? In-Reply-To: References: Message-ID: I wrote the initial implementation of the LLVM code generator many years ago now. At the time, no Haskell bindings suitable for block code generation existed. I was doing the work as per of an undergraduate thesis and so with time pressures went with the quicker option of producing a text file rather than implementing bindings. That said, there are advantages of this approach: The LLVM backend can ship with GHC by default as it has no dependency on LLVM libraries. Not worrying about packaging or linking against LLVM for a new experimental backend was great. I also don't believe we loose much speed by going through the file system. When I last tried to measure this, 75% of the time for the LLVM code generation was spent in optimization, less than 10% in parsing the file. These were rough numbers so perhaps I made a mistake in measuring them. The text file format also was originally white stable and so made it easy to choose different LLVM versions. This has become more of a problem as time has progressed, so there is a push to bundle LLVM with GHC to fix on one version. Cheers David > On Jun 3, 2016, at 8:25 AM, Nicola Gigante wrote: > > Hi all, > > while looking at the GHC 8 Trac page I encountered the page > about the plans for the improved LLVM backend: > > https://ghc.haskell.org/trac/ghc/wiki/ImprovedLLVMBackend > > I know nearly nothing about the internals of the GHC backend so > I may be asking something trivial, but from reading that page > I understand that GHC currently calls LLVM command line tools > to optimize and compile the IR, is it right? > > LLVM is a C++ library, but it also exports a portable and stable C API > which I think is already covered by the llvm-general package. > > So as someone who worked on LLVM in the past, and appreciated > its library-based integration-friendly design I?m wondering why is > GHC using the command line tools instead of linking to the library? > > Best Regards, > Nicola > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Mon Jun 6 02:31:10 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sun, 5 Jun 2016 22:31:10 -0400 Subject: x86-64 unknown-linux Message-ID: Hi devs, I would like to download GHC 8 binaries for Arch Linux on an x86-64 architecture. I assume I'm looking for an unknown-linux build, and it looks like what I want is a Tier 1 platform, according to https://ghc.haskell.org/trac/ghc/wiki/Platforms Yet I don't see this release in https://downloads.haskell.org/~ghc/8.0.1/ Can you help? Thanks! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From austin at well-typed.com Mon Jun 6 02:46:39 2016 From: austin at well-typed.com (Austin Seipp) Date: Sun, 5 Jun 2016 21:46:39 -0500 Subject: x86-64 unknown-linux In-Reply-To: References: Message-ID: On Linux, the builds are keyed by the OS name they were built on. This is because systems like CentOS have different versions of libgmp, glibc than e.g. Debian derivatives. So they actually refer to different paths, are built against different APIs depending on what's available, etc. That's why the names are distinguished; in the past only Debian-based builds were offered, but I started building CentOS versions in the 7.8.x era. The debian-based builds are normally the 'lowest common denominator' that works on all modern systems. Given that, you want: https://downloads.haskell.org/~ghc/8.0.1/ghc-8.0.1-x86_64-deb8-linux.tar.xz If you have a problem, just yell. On Sun, Jun 5, 2016 at 9:31 PM, Richard Eisenberg wrote: > Hi devs, > > I would like to download GHC 8 binaries for Arch Linux on an x86-64 > architecture. I assume I'm looking for an unknown-linux build, and it looks > like what I want is a Tier 1 platform, according to > https://ghc.haskell.org/trac/ghc/wiki/Platforms Yet I don't see this > release in https://downloads.haskell.org/~ghc/8.0.1/ > > Can you help? > > Thanks! > Richard > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -- Regards, Austin Seipp, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Mon Jun 6 09:08:10 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Mon, 6 Jun 2016 10:08:10 +0100 Subject: Harbourmaster is still not building diffs Message-ID: Since a couple of months ago, harbourmaster no longer builds diffs. This is quite a large barrier to entry for new contributors as running ./validate takes a long time. It seems to be a very low priority issue to get it back working. Are there plans to get harbourmaster to build diffs again? Matt From hvriedel at gmail.com Mon Jun 6 11:30:10 2016 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Mon, 06 Jun 2016 13:30:10 +0200 Subject: Proposal: Left-Associative Semigroup Operator Alias in "Data.Semigroup" Message-ID: <87d1nupnb1.fsf@gnu.org> Hello! In short, the right-associative fixity of (Data.{Monoid,Semigroup}.<>) subtly conflicts with definitions of (<>) in pretty printing APIs, for which the left-associative variant is sometimes desirable. This subtle overloading of (<>) is error-prone, as one has to remember which version of (<>) is currently in scope in order to be able to reason about non-trivial expressions involving this operator. This proposal is an attempt to resolve this unfortunate and confusing situation by completing the `Semigroup`/`Monoid` vocabulary with a standard left-associative alias. Please see https://ghc.haskell.org/trac/ghc/wiki/Proposal/LeftAssocSemigroupOp for more details. Discussion period: 4 weeks -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 818 bytes Desc: not available URL: From eir at cis.upenn.edu Mon Jun 6 13:58:03 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Mon, 6 Jun 2016 09:58:03 -0400 Subject: x86-64 unknown-linux In-Reply-To: References: Message-ID: <3518ADFF-D872-4794-868E-62BFC8092CDE@cis.upenn.edu> On Jun 5, 2016, at 10:46 PM, Austin Seipp wrote: > On Linux, the builds are keyed by the OS name they were built on. This is because systems like CentOS have different versions of libgmp, glibc than e.g. Debian derivatives. So they actually refer to different paths, are built against different APIs depending on what's available, etc. That's why the names are distinguished; in the past only Debian-based builds were offered, but I started building CentOS versions in the 7.8.x era. > > The debian-based builds are normally the 'lowest common denominator' that works on all modern systems. Given that, you want: > > https://downloads.haskell.org/~ghc/8.0.1/ghc-8.0.1-x86_64-deb8-linux.tar.xz Thanks for this explanation. If that's the go-to distribution for any arbitrary linux, perhaps we should make a symlink with "unknown-linux" point to it. To be clear, I don't really know what I'm talking about, but I do see that many other directories on downloads.haskell.org/~ghc have "unknown-linux" options and I feel safer using that than a binary for a distribution I don't have. In any case, thanks for the clarification! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Mon Jun 6 16:37:33 2016 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Mon, 06 Jun 2016 16:37:33 +0000 Subject: Moving ArgumentsDo forward In-Reply-To: References: Message-ID: As the author of the proposal and extension, I'd like to clarify that the change was abandoned per se because of how controversial the change was. [0] [1] [2] This is not to say that we should not continue to discuss this change, but if we do so, make sure that you first read through the previous discussion -- it was quite extensive! Specifically, I became unconvinced that it was worth the effort to make as an extension, given the reasons against it (mainly, extra work for GHC, hindent, haskell-src-exts, etc etc); I think this along with a few other things (trailing commas!) could make a significant improvement to cosmetic Haskell syntax, but perhaps one extension per character is a bit much for that. That said I have no idea how else a mythical Haskell' could get a cleaned up syntax if not through first being implemented as a GHC extension. Finally, you may be interested in ghc-reskin [3], which was a (slightly tongue-in-cheek) response to a lot of the discussion caused by this extension last time, and could potentially be made into a production-ready tool / Haskell' syntax if anyone cared strongly to do so. [0] https://www.reddit.com/r/haskell/comments/447bnw/does_argument_do_have_a_future/ [1] https://mail.haskell.org/pipermail/haskell-cafe/2015-September/121217.html [2] https://ghc.haskell.org/trac/ghc/ticket/10843 [3] https://github.com/gibiansky/ghc-reskin Best, Andrew On Wed, Jun 1, 2016 at 3:26 PM Akio Takano wrote: > Hi Bardur, > > On 2 June 2016 at 00:09, Bardur Arantsson wrote: > > On 06/01/2016 01:48 PM, Akio Takano wrote: > >> Hi, > >> > >> Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would > >> love to see in GHC. It's a small syntactic extension that allows do, > >> case, if and lambda blocks as function arguments, without parentheses. > >> However, its differential revision [1] has been abandoned, citing a > >> mixed response from the community. A message [2] on the ticket > >> summarizes a thread in haskell-cafe on this topic. > >> > >> I, for one, think adding this extension is worthwhile, because a > >> significant number of people support it. Also, given how some people > >> seem to feel ambivalent about this change, I believe actually allowing > >> people to try it makes it clearer whether it is a good idea. > >> > >> Thus I'm wondering: is there any chance that this gets merged? If so, > >> I'm willing to work on whatever is remaining to get the change merged. > >> > > > > What's changed since it was last discussed? > > Nothing has really changed. I'm just trying to argue that the current > level of community support is good enough to justify an > implementation. > > Please note that the previous Differential revision was abandoned by > the author. It was *not* rejected due to a lack of support. Hence my > question: if properly implemented, does this feature have any chance > of getting merged in, or is it regarded too controversial? > > > I don't think the objections > > were centered in the implementation, so I don't see what "whatever is > > remaining to get the change merged" would be. > > I'm referring the points mentioned in the review comments in the > Differential revision. For example this change needs an update to the > User's Guide. > > > > > AFAICT at best it's a *very* small improvement[1] and fractures Haskell > > syntax even more around extensions -- tooling etc. will need to > > understand even *more* syntax extensions[2]. > > I disagree that this is a small improvement, but I don't intend to > debate this here. As you said, nothing has really changed since it was > discussed before, and a lot of reasons for implementing this extension > have been already pointed out. I don't have anything to add. > > Regarding tooling, my understanding is that most tools that need to > understand Haskell (this includes ghc-mod and hdevtools) use either > the GHC API or haskell-src-exts, so I don't think this extension would > need changes in many places. > > Regards, > Takano Akio > > > > > Regards, > > > > [1] If you grant that it is indeed an improvment, which I, personally, > > don't think it is. > > > > [2] I think most people agree that this is something that should perhaps > > be handled by something like > > https://github.com/haskell/haskell-ide-engine so that it would only need > > to be implemented once, but there's not even an alpha release yet, so > > that particular objection stands, AFAICT. > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -- ? Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From bergey at teallabs.org Mon Jun 6 16:48:01 2016 From: bergey at teallabs.org (Daniel Bergey) Date: Mon, 06 Jun 2016 12:48:01 -0400 Subject: Proposal: Left-Associative Semigroup Operator Alias in "Data.Semigroup" In-Reply-To: <87d1nupnb1.fsf@gnu.org> References: <87d1nupnb1.fsf@gnu.org> Message-ID: <87a8iye01q.fsf@chladni.i-did-not-set--mail-host-address--so-tickle-me> I've often needed to use Semigroup <> and pretty-print <> in the same module. Thanks for trying to improve the situation. Are there other Semigroups where people want the right-associative > b <+> c` occur more often than `a <+> b <> c`? Or is that just an artifact of the pretty-printing <> being left-associative? If I understand the proposed migration path, upgrading `pretty` without changing my code would silently change semantics. Upgrading correctly requires s/<>/>< locally. This leaves me with a funny (><) operator that seems mostly historical, and still the surprising behavior of `a <+> b >< c`. This doesn't seem like an attractive migration for anywhere I use pretty-printing. Maybe it's still the best answer for GHC internal use; I can't tell. cheers, bergey Footnotes: [1] https://github.com/haskell/pretty/issues/30#issuecomment-161146748 On 2016-06-06 at 07:30, Herbert Valerio Riedel wrote: > Hello! > > In short, the right-associative fixity of (Data.{Monoid,Semigroup}.<>) > subtly conflicts with definitions of (<>) in pretty printing APIs, for > which the left-associative variant is sometimes desirable. This subtle > overloading of (<>) is error-prone, as one has to remember which version > of (<>) is currently in scope in order to be able to reason about > non-trivial expressions involving this operator. > > This proposal is an attempt to resolve this unfortunate and confusing > situation by completing the `Semigroup`/`Monoid` vocabulary with a > standard left-associative alias. Please see > > https://ghc.haskell.org/trac/ghc/wiki/Proposal/LeftAssocSemigroupOp > > for more details. > > Discussion period: 4 weeks > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From djsamperi at gmail.com Mon Jun 6 21:02:12 2016 From: djsamperi at gmail.com (Dominick Samperi) Date: Mon, 6 Jun 2016 17:02:12 -0400 Subject: Why upper bound version numbers? Message-ID: Why would a package developer want to upper bound the version number for packages like base? For example, the clash package requires base >= 4.2 && base <= 4.3 Consequently, it refuses to install with the latest ghc provided with the Haskell Platform (8.0.1). Does this mean that assuming that future versions of the platform will remain backwards compatible with prior versions is unsafe? Thanks, Dominick From allbery.b at gmail.com Mon Jun 6 21:13:11 2016 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 6 Jun 2016 17:13:11 -0400 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: On Mon, Jun 6, 2016 at 5:02 PM, Dominick Samperi wrote: > Consequently, it refuses to install with the latest ghc provided with > the Haskell Platform (8.0.1). > base is not defined by the Platform, it is defined by (and ships with, and must completely match) ghc. And no, backward compatibility is not guaranteed; for a recent example, ghc 7.10 broke many programs by making Applicative a "superclass" of Monad and by generalizing many Prelude functions to Foldable and/or Traversable. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From djsamperi at gmail.com Tue Jun 7 00:19:25 2016 From: djsamperi at gmail.com (Dominick Samperi) Date: Mon, 6 Jun 2016 20:19:25 -0400 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: The odd thing about this is that to upper bound a package that you did not write (like base) you would have to know that incompatible changes were coming in subsequent revisions, or that features of the API that you rely on will be changed. The upper bound makes perfect sense for packages that you are maintaining. Perhaps the answer to my original question is that the maintainer of clash is also maintaining (part of) base? On Mon, Jun 6, 2016 at 5:13 PM, Brandon Allbery wrote: > On Mon, Jun 6, 2016 at 5:02 PM, Dominick Samperi > wrote: >> >> Consequently, it refuses to install with the latest ghc provided with >> the Haskell Platform (8.0.1). > > > base is not defined by the Platform, it is defined by (and ships with, and > must completely match) ghc. > And no, backward compatibility is not guaranteed; for a recent example, ghc > 7.10 broke many programs by making Applicative a "superclass" of Monad and > by generalizing many Prelude functions to Foldable and/or Traversable. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net From allbery.b at gmail.com Tue Jun 7 00:22:27 2016 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 6 Jun 2016 20:22:27 -0400 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: On Mon, Jun 6, 2016 at 8:19 PM, Dominick Samperi wrote: > The odd thing about this is that to upper bound a package that you did > not write (like base) you would have to know that incompatible changes > were coming in subsequent revisions, or that features of the API that > you rely on will be changed. > There is a versioning policy covering this. It has been found to be necessary because otherwise people who try to build packages find themselves with broken messes because of the assumption that any future version of a package is guaranteed to be compatible. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From djsamperi at gmail.com Tue Jun 7 00:58:34 2016 From: djsamperi at gmail.com (Dominick Samperi) Date: Mon, 6 Jun 2016 20:58:34 -0400 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: I guess what you are saying is that this policy will prevent packages from installing with new versions of ghc until the maintainer has had a chance to test the package with the new version, and has updated the upper version limit. Thus, inserting those upper version limits is a kind of flag that indicates that the package has been "certified" for use with versions of base less than or equal to the upper limit. On Mon, Jun 6, 2016 at 8:22 PM, Brandon Allbery wrote: > On Mon, Jun 6, 2016 at 8:19 PM, Dominick Samperi > wrote: >> >> The odd thing about this is that to upper bound a package that you did >> not write (like base) you would have to know that incompatible changes >> were coming in subsequent revisions, or that features of the API that >> you rely on will be changed. > > > There is a versioning policy covering this. It has been found to be > necessary because otherwise people who try to build packages find themselves > with broken messes because of the assumption that any future version of a > package is guaranteed to be compatible. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net From xichekolas at gmail.com Tue Jun 7 06:14:01 2016 From: xichekolas at gmail.com (Andrew Farmer) Date: Mon, 6 Jun 2016 23:14:01 -0700 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: Aforementioned versioning policy: https://wiki.haskell.org/Package_versioning_policy On Mon, Jun 6, 2016 at 5:58 PM, Dominick Samperi wrote: > I guess what you are saying is that this policy will prevent packages > from installing with new versions of ghc until the maintainer has had > a chance to test the package with the new version, and has updated the > upper version limit. Thus, inserting those upper version limits is a > kind of flag that indicates that the package has been "certified" for > use with versions of base less than or equal to the upper limit. > > On Mon, Jun 6, 2016 at 8:22 PM, Brandon Allbery wrote: >> On Mon, Jun 6, 2016 at 8:19 PM, Dominick Samperi >> wrote: >>> >>> The odd thing about this is that to upper bound a package that you did >>> not write (like base) you would have to know that incompatible changes >>> were coming in subsequent revisions, or that features of the API that >>> you rely on will be changed. >> >> >> There is a versioning policy covering this. It has been found to be >> necessary because otherwise people who try to build packages find themselves >> with broken messes because of the assumption that any future version of a >> package is guaranteed to be compatible. >> >> -- >> brandon s allbery kf8nh sine nomine associates >> allbery.b at gmail.com ballbery at sinenomine.net >> unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From hvriedel at gmail.com Tue Jun 7 06:15:04 2016 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 07 Jun 2016 08:15:04 +0200 Subject: Why upper bound version numbers? In-Reply-To: (Dominick Samperi's message of "Mon, 6 Jun 2016 20:58:34 -0400") References: Message-ID: <878tyhplsn.fsf@gmail.com> On 2016-06-07 at 02:58:34 +0200, Dominick Samperi wrote: > I guess what you are saying is that this policy will prevent packages > from installing with new versions of ghc until the maintainer has had > a chance to test the package with the new version, and has updated the > upper version limit. Thus, inserting those upper version limits is a > kind of flag that indicates that the package has been "certified" for > use with versions of base less than or equal to the upper limit. That's one important aspect. I'm very distrustful of packages whose maintainers declares that their packages have eternal future compatibility (unless they have made this decision *very* carefully based on which parts of the API they use). In general, this runs into the fallacy that successful compilation would be equivalent to (semantic) API compatibility, which is only half the story. In some cases one may be lucky to get compile-time warnings (which are often ignored anyway), or explicit run-time errors (which are still undesirable), or even worse silent failures where the code behaves subtly wrong or different than expected. Testsuites mitigate this to some degree, but they too are an imperfect solution to this hard problem. So another aspect is that the PVP[1] provides an API contract which makes upper bounds possible at all (for packages you don't control). While the PVP doesn't give you a way to know for sure when compatibility breaks, the policy gives you a least upper bound up to which your package is guaranteed (under certain conditions) to remain compatible. Without this contract, you'd have no choice but to constraint your package to versions of dependencies (not under your control) which you were able to empirically certify to be compatible semantically, i.e. versions that were already published. Unfortunately, GHC's `base` package has a *huge* API surface. So with each GHC release we're usually forced to perform a major version bump to satisfy the PVP, even if just a tiny part only very few packages use of `base`'s API became backward in-compatible. This may be addressed by reducing the API surface of `base` by moving infrequently used GHC-internal-ish parts of the API out of base. But there's also other changes which affect many more packages as already mentioned. As already mentioned, the big AMP change was a major breaking point. Some packages like http://matrix.hackage.haskell.org/package/unordered-containers tend to break every time a new GHC version comes out. Partly because they happen to use the low-level parts of `base` API which tend to change. Ironically, in the case of `unordered-containers`, the maintainer decided to start leaving off (or rather make ineffective) the upper bound on `base` starting with 0.2.2.0, and this turned to be an error in judgment, as each time a new GHC version came out, the very bound that was left out would turned out to be necessary. So leaving off upper bounds created actually more work and no benefit in the case of `unordered-containers`. [1]: https://wiki.haskell.org/Package_versioning_policy From christiaan.baaij at gmail.com Tue Jun 7 08:29:34 2016 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Tue, 7 Jun 2016 10:29:34 +0200 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: <575685EE.7040808@gmail.com> Given that I'm the maintainer of the 'clash' package, I wanted to say that the 'clash' package has been deprecated in favour of the 'clash-ghc' package (for some time now, and this is stated on hackage). Sadly, 'clash-ghc' will not compile on ghc 8.0.1 right now either; it only compiles against ghc 7.10. I will update the installation instructions on the website and in the haddock documentation to mention this fact. A version of 'clash-ghc' that compiles against 8.0.1 is not due for another month. If you have any more questions about installing clash, I strongly encourage you to either email me, or the clash-mailing list (http://groups.google.com/group/clash-language), and not use this mailing list (ghc-devs at haskell.org) for question about clash. Regards, Christiaan On 06/06/2016 11:02 PM, Dominick Samperi wrote: > Why would a package developer want to upper bound the version number > for packages like base? For example, the clash package requires > > base >= 4.2 && base <= 4.3 > > Consequently, it refuses to install with the latest ghc provided with > the Haskell Platform (8.0.1). > > Does this mean that assuming that future versions of the platform will > remain backwards compatible with prior versions is unsafe? > > Thanks, > Dominick > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From hesselink at gmail.com Tue Jun 7 08:43:14 2016 From: hesselink at gmail.com (Erik Hesselink) Date: Tue, 7 Jun 2016 10:43:14 +0200 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: Others have already commented on many aspects of this discussion, but I just wanted to mention that cabal has an '--allow-newer' flag to disregard these constraints, so '--allow-newer=base' would allow you to try and compile this package with GHC 8. Since GHC 8 is very recent though and base 4.3 is very old, I imagine it won't work. In general I think many packages haven't been updated for GHC 8 yet. Erik On 6 June 2016 at 23:02, Dominick Samperi wrote: > Why would a package developer want to upper bound the version number > for packages like base? For example, the clash package requires > > base >= 4.2 && base <= 4.3 > > Consequently, it refuses to install with the latest ghc provided with > the Haskell Platform (8.0.1). > > Does this mean that assuming that future versions of the platform will > remain backwards compatible with prior versions is unsafe? > > Thanks, > Dominick > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From simonpj at microsoft.com Tue Jun 7 09:00:35 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 7 Jun 2016 09:00:35 +0000 Subject: Help! Windows build broken in teestsuite Message-ID: <35c1dc4ee02b455196154d6c3129ec1b@DB4PR30MB030.064d.mgd.msft.net> Aargh! The Windows build is broken again. This time it?s the testsuite. It seems to be trying to run the test in a temp directory, and failing to find the directory. Thomie, could this be something to do with your work on the testsuite? Please fix! Or tell me what to revert. It leaves me stuck. Thanks Simon /cygdrive/c/code/HEAD/testsuite/tests/indexed-types/should_fail$ make TEST=T9662 PYTHON="python" "python" ../../../driver/runtests.py -e ghc_compiler_always_flags="'-fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-warn-missed-specialisations -fshow-warning-groups '" -e ghc_debugged=False -e ghc_with_native_codegen=1 -e ghc_with_vanilla=1 -e ghc_with_dynamic=0 -e ghc_with_profiling=0 -e ghc_with_threaded_rts=1 -e ghc_with_dynamic_rts=0 -e ghc_with_interpreter=1 -e ghc_unregisterised=0 -e ghc_dynamic_by_default=False -e ghc_dynamic=False -e ghc_with_smp=1 -e ghc_with_llvm=0 -e windows=True -e darwin=False -e in_tree_compiler=True -e cleanup=True --rootdir=. --configfile=../../../config/ghc -e 'config.confdir="../../../config"' -e 'config.platform="x86_64-unknown-mingw32"' -e 'config.os="mingw32"' -e 'config.arch="x86_64"' -e 'config.wordsize="64"' -e 'config.timeout=int() or config.timeout' -e 'config.exeext=".exe"' -e 'config.top="/cygdrive/c/code/HEAD/testsuite"' --config 'compiler="/cygdrive/c/code/HEAD/inplace/bin/ghc-stage2.exe"' --config 'ghc_pkg="/cygdrive/c/code/HEAD/inplace/bin/ghc-pkg.exe"' --config 'haddock=' --config 'hp2ps="/cygdrive/c/code/HEAD/inplace/bin/hp2ps.exe"' --config 'hpc="/cygdrive/c/code/HEAD/inplace/bin/hpc.exe"' --config 'gs="gs"' --config 'timeout_prog="../../../timeout/install-inplace/bin/timeout.exe"' \ --only=T9662 \ \ \ \ \ \ Timeout is 300 Found 1 .T files... Beginning test run at 06/07/16 07:45:13 GMT Summer Time ====> Scanning ./all.T =====> T9662(normal) 1 of 1 [0, 0, 0] cd c:/users/simonpj/appdata/local/temp/ghctest-qbd2zw\1\2\3\.\T9662 && "C:/code/HEAD/inplace/bin/ghc-stage2.exe" -c T9662.hs -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-warn-missed-specialisations -fshow-warning-groups -fno-ghci-history > T9662.comp.stderr 2>&1 sh: line 0: cd: c:/users/simonpj/appdata/local/temp/ghctest-qbd2zw123.T9662: No such file or directory -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Tue Jun 7 09:00:03 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Tue, 7 Jun 2016 05:00:03 -0400 Subject: Do we need to maintain PrimRep.VecRep? Message-ID: I have some code that does things depending on PrimReps of terms and so I have to handle VecRep there. To understand what VecRep exactly is and how to use it I looked at its uses, and all I can find was that we have a wired-in DataCon `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but when I test in GHCi I see that its PrimRep is PtrRep: ?> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon)) [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] (This DataCon is not exported and only used in runtimeRepTyCon) So I think VecRep may not be in use at the moment. Do we still need to maintain it? What's the use case? Can anyone show me a Core term that has a type whose PrimRep is VecRep? Thanks.. From benl at ouroborus.net Tue Jun 7 13:31:49 2016 From: benl at ouroborus.net (Ben Lippmeier) Date: Tue, 7 Jun 2016 23:31:49 +1000 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> > On 7 Jun 2016, at 7:02 am, Dominick Samperi wrote: > > Why would a package developer want to upper bound the version number > for packages like base? For example, the clash package requires > > base >= 4.2 && base <= 4.3 I put an upper bound on all my libraries as a proxy for the GHC version. Each time a new GHC version is released sometimes my libraries work with it and sometimes not. I remember a ?burning bridges? event in recent history, when the definition of the Monad class changed and broke a lot of things. Suppose you maintain a library that is used by a lot of first year uni students (like gloss). Suppose the next GHC version comes around and your library hasn?t been updated yet because you?re waiting on some dependencies to get fixed before you can release your own. Do you want your students to get a ?cannot install on this version? error, or some confusing build error which they don?t understand? The upgrade process could be automated with a buildbot: it would try new versions and automatically bump the upper bound if the regression tests worked, but someone would need to implement it. > Does this mean that assuming that future versions of the platform will > remain backwards compatible with prior versions is unsafe? My experience so far is that new GHC versions are ?mostly? backwards compatible, but there are often small details that break library builds anyway. It only takes a day or so per year to fix, so I don?t mind too much. Ben. From mainland at apeiron.net Tue Jun 7 14:48:58 2016 From: mainland at apeiron.net (Geoffrey Mainland) Date: Tue, 7 Jun 2016 10:48:58 -0400 Subject: Do we need to maintain PrimRep.VecRep? In-Reply-To: References: Message-ID: <5756DEDA.1050004@apeiron.net> VecRep is used for vector operations. If you aren't using LLVM, you won't see them. VecRep's are generated by utils/genprimopcode/Main.hs. Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build tree---should be plenty of generated VecRep's there :) Cheers, Geoff On 06/07/2016 05:00 AM, ?mer Sinan A?acan wrote: > I have some code that does things depending on PrimReps of terms and so I have > to handle VecRep there. To understand what VecRep exactly is and how to use it I > looked at its uses, and all I can find was that we have a wired-in DataCon > `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but > when I test in GHCi I see that its PrimRep is PtrRep: > > ?> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon)) > [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] > > (This DataCon is not exported and only used in runtimeRepTyCon) > > So I think VecRep may not be in use at the moment. Do we still need to maintain > it? What's the use case? Can anyone show me a Core term that has a type whose > PrimRep is VecRep? > > Thanks.. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From omeragacan at gmail.com Tue Jun 7 15:08:08 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Tue, 7 Jun 2016 11:08:08 -0400 Subject: Do we need to maintain PrimRep.VecRep? In-Reply-To: <5756DEDA.1050004@apeiron.net> References: <5756DEDA.1050004@apeiron.net> Message-ID: Thanks, I can see the TyCons with VecReps there.. but I still can't see how the terms are constructed? Can you show me some example programs, or functions in the compiler, that generate vector terms? (e.g. terms with types with VecReps) 2016-06-07 10:48 GMT-04:00 Geoffrey Mainland : > VecRep is used for vector operations. If you aren't using LLVM, you > won't see them. > > VecRep's are generated by utils/genprimopcode/Main.hs. > > Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build > tree---should be plenty of generated VecRep's there :) > > Cheers, > Geoff > > On 06/07/2016 05:00 AM, ?mer Sinan A?acan wrote: >> I have some code that does things depending on PrimReps of terms and so I have >> to handle VecRep there. To understand what VecRep exactly is and how to use it I >> looked at its uses, and all I can find was that we have a wired-in DataCon >> `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but >> when I test in GHCi I see that its PrimRep is PtrRep: >> >> ?> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon)) >> [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] >> >> (This DataCon is not exported and only used in runtimeRepTyCon) >> >> So I think VecRep may not be in use at the moment. Do we still need to maintain >> it? What's the use case? Can anyone show me a Core term that has a type whose >> PrimRep is VecRep? >> >> Thanks.. >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From mainland at apeiron.net Tue Jun 7 15:22:56 2016 From: mainland at apeiron.net (Geoffrey Mainland) Date: Tue, 7 Jun 2016 11:22:56 -0400 Subject: Do we need to maintain PrimRep.VecRep? In-Reply-To: References: <5756DEDA.1050004@apeiron.net> Message-ID: <5756E6D0.9080501@apeiron.net> Only programs that use vector primops will generate VecRep's. GHC is not such a program. The branch of vector that I modified to use vector primops will generate VecRep's. You can find it here: https://github.com/mainland/vector/tree/simd It uses a modified version of primitive. See here, for example: https://github.com/mainland/primitive/blob/simd/Data/Primitive/Multi.hs The reason this is not available more widely is lack of support in the native code generator. Do you have any interest in working on adding such support? :) Cheers, Geoff On 06/07/2016 11:08 AM, ?mer Sinan A?acan wrote: > Thanks, I can see the TyCons with VecReps there.. but I still can't see how the > terms are constructed? Can you show me some example programs, or functions in > the compiler, that generate vector terms? (e.g. terms with types with VecReps) > > 2016-06-07 10:48 GMT-04:00 Geoffrey Mainland : >> VecRep is used for vector operations. If you aren't using LLVM, you >> won't see them. >> >> VecRep's are generated by utils/genprimopcode/Main.hs. >> >> Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build >> tree---should be plenty of generated VecRep's there :) >> >> Cheers, >> Geoff >> >> On 06/07/2016 05:00 AM, ?mer Sinan A?acan wrote: >>> I have some code that does things depending on PrimReps of terms and so I have >>> to handle VecRep there. To understand what VecRep exactly is and how to use it I >>> looked at its uses, and all I can find was that we have a wired-in DataCon >>> `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but >>> when I test in GHCi I see that its PrimRep is PtrRep: >>> >>> ?> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon)) >>> [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] >>> >>> (This DataCon is not exported and only used in runtimeRepTyCon) >>> >>> So I think VecRep may not be in use at the moment. Do we still need to maintain >>> it? What's the use case? Can anyone show me a Core term that has a type whose >>> PrimRep is VecRep? >>> >>> Thanks.. >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From omeragacan at gmail.com Tue Jun 7 15:49:56 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Tue, 7 Jun 2016 11:49:56 -0400 Subject: Do we need to maintain PrimRep.VecRep? In-Reply-To: <5756E6D0.9080501@apeiron.net> References: <5756DEDA.1050004@apeiron.net> <5756E6D0.9080501@apeiron.net> Message-ID: Ahh, I see... I finally found the primops, machops, and code generator for x86: MO_V_Insert {} -> needLlvm MO_V_Extract {} -> needLlvm MO_V_Add {} -> needLlvm MO_V_Sub {} -> needLlvm ... > The reason this is not available more widely is lack of support in the native > code generator. Do you have any interest in working on adding such support? > :) I'm afraid I'm short on free time at the moment but I'll let you know if I have a chance to work on that. Thanks, Omer 2016-06-07 11:22 GMT-04:00 Geoffrey Mainland : > Only programs that use vector primops will generate VecRep's. GHC is not > such a program. > > The branch of vector that I modified to use vector primops will generate > VecRep's. You can find it here: > > https://github.com/mainland/vector/tree/simd > > It uses a modified version of primitive. See here, for example: > > https://github.com/mainland/primitive/blob/simd/Data/Primitive/Multi.hs > > The reason this is not available more widely is lack of support in the > native code generator. Do you have any interest in working on adding > such support? :) > > Cheers, > Geoff > > On 06/07/2016 11:08 AM, ?mer Sinan A?acan wrote: >> Thanks, I can see the TyCons with VecReps there.. but I still can't see how the >> terms are constructed? Can you show me some example programs, or functions in >> the compiler, that generate vector terms? (e.g. terms with types with VecReps) >> >> 2016-06-07 10:48 GMT-04:00 Geoffrey Mainland : >>> VecRep is used for vector operations. If you aren't using LLVM, you >>> won't see them. >>> >>> VecRep's are generated by utils/genprimopcode/Main.hs. >>> >>> Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build >>> tree---should be plenty of generated VecRep's there :) >>> >>> Cheers, >>> Geoff >>> >>> On 06/07/2016 05:00 AM, ?mer Sinan A?acan wrote: >>>> I have some code that does things depending on PrimReps of terms and so I have >>>> to handle VecRep there. To understand what VecRep exactly is and how to use it I >>>> looked at its uses, and all I can find was that we have a wired-in DataCon >>>> `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but >>>> when I test in GHCi I see that its PrimRep is PtrRep: >>>> >>>> ?> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon)) >>>> [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] >>>> >>>> (This DataCon is not exported and only used in runtimeRepTyCon) >>>> >>>> So I think VecRep may not be in use at the moment. Do we still need to maintain >>>> it? What's the use case? Can anyone show me a Core term that has a type whose >>>> PrimRep is VecRep? >>>> >>>> Thanks.. >>>> _______________________________________________ >>>> ghc-devs mailing list >>>> ghc-devs at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From howard_b_golden at yahoo.com Tue Jun 7 17:15:00 2016 From: howard_b_golden at yahoo.com (Howard B. Golden) Date: Tue, 7 Jun 2016 17:15:00 +0000 (UTC) Subject: Suggestions for improving the PVP. Was Re: Why upper bound version numbers? In-Reply-To: <878tyhplsn.fsf@gmail.com> References: <878tyhplsn.fsf@gmail.com> Message-ID: <1998682129.580886.1465319700828.JavaMail.yahoo@mail.yahoo.com> On Monday, June 6, 2016 23:15:00 -0700, Herbert Valerio Riedel wrote: > Unfortunately, GHC's `base` package has a *huge* API surface. So with> each GHC release we're usually forced to perform a major version bump to > satisfy the PVP, even if just a tiny part only very few packages use of > `base`'s API became backward in-compatible. This may be addressed by > reducing the API surface of `base` by moving infrequently used > GHC-internal-ish parts of the API out of base. 1. I hope the compartmenting of `base` will be done soon. The PVP's purpose is subverted by the frequent churning of `base` versions. 2. On /r/haskell I suggested that a package's dependencies be treated as metadata that can be maintained independently of the package itself. For example, if `foo-x.y.z.w` works with dependency `bar-a.b.c.d`, this would be included in `foo`'s .cabal file (the current practice). However, if a new version of `bar` is later found to be compatible, this fact would be stored in the external metadata (without having to update `foo-x.y.z.w`'s .cabal file), and cabal would look at this external metadata when calculating acceptable versions of `bar`. This would avoid *unnecessary* domino updates to packages in cases when their dependencies are updated in a compatible fashion. 3. In general, the granularity of package versions tracked by the PVP should be reconsidered. Ideally, each externally visible function should be tracked separately, which would allow using upward compatible versions of packages in many more cases than the PVP allows at present. Whether this finer granularity would be worth the added complexity should be given a fair trial. This tracking could be partially automated with a tool to compare the current package version with its update to identify formal changes. Semantic changes would still have to be noted manually. Howard From simonpj at microsoft.com Tue Jun 7 20:40:59 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 7 Jun 2016 20:40:59 +0000 Subject: Testsuite total failure on Windows Message-ID: Thomie Is this you working on my show-stopping problem with the tetssuite? sh: line 0: cd: c:/users/simonpj/appdata/local/temp/ghctest-qbd2zw123.T9662: No such file or directory If so, thank you! If not, might you look (email attached). I am so stuck. Even a commit to roll back would be fine. But I don't know where to start. Thanks Simon | -----Original Message----- | From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of | git at git.haskell.org | Sent: 07 June 2016 20:33 | To: ghc-commits at haskell.org | Subject: [commit: ghc] wip/thomie: Testsuite driver: always quote | opts.testdir (9bee6ef) | | Repository : ssh://git at git.haskell.org/ghc | | On branch : wip/thomie | Link : | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fghc.haskell.o | rg%2ftrac%2fghc%2fchangeset%2f9bee6ef2fb5c280e061144368d75a0ef947e68c9%2fghc& | data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c511d448661614206dbb808d38f0 | b2182%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=uOhvqGkrC3j2fRIYwTeDZ28%2f | x58jMs5jh1BdUDMiERY%3d | | >--------------------------------------------------------------- | | commit 9bee6ef2fb5c280e061144368d75a0ef947e68c9 | Author: Thomas Miedema | Date: Tue Jun 7 15:59:15 2016 +0200 | | Testsuite driver: always quote opts.testdir | | This makes sure the testsuite keeps working when testdir contains | backward slashes. | | | >--------------------------------------------------------------- | | 9bee6ef2fb5c280e061144368d75a0ef947e68c9 | testsuite/driver/runtests.py | 2 +- | testsuite/driver/testlib.py | 42 +++++++++++++++++++------------ | -- | testsuite/tests/cabal/cabal01/Makefile | 2 +- | testsuite/tests/ghci/linking/dyn/all.T | 4 ++-- | testsuite/tests/rename/prog006/Makefile | 2 +- | 5 files changed, 29 insertions(+), 23 deletions(-) | | Diff suppressed because of size. To see it, use: | | git diff-tree --root --patch-with-stat --no-color --find-copies-harder -- | ignore-space-at-eol --cc 9bee6ef2fb5c280e061144368d75a0ef947e68c9 | _______________________________________________ | ghc-commits mailing list | ghc-commits at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell. | org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | commits&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c511d448661614206dbb | 808d38f0b2182%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=2%2bhPH%2bwQOwvVTE | QdWNZZBmPziSwaudLrYp4DCOGXct8%3d -------------- next part -------------- An embedded message was scrubbed... From: Simon Peyton Jones Subject: Help! Windows build broken in teestsuite Date: Tue, 7 Jun 2016 09:00:35 +0000 Size: 15402 URL: From thomasmiedema at gmail.com Tue Jun 7 21:44:48 2016 From: thomasmiedema at gmail.com (Thomas Miedema) Date: Tue, 7 Jun 2016 23:44:48 +0200 Subject: Testsuite total failure on Windows In-Reply-To: References: Message-ID: Hi Simon, Is this you working on my show-stopping problem with the tetssuite? > sh: line 0: cd: > c:/users/simonpj/appdata/local/temp/ghctest-qbd2zw123.T9662: No such file > or directory > I pushed a fix. It was my mistake. It turns out there are 2 types of Python on Windows (msys2 and mingw), and the way they handle paths (and also unicode) is subtly different. This also explains why you sometimes see validate failures that others don't (such as T5975a). But now I know the cause, so we can do something about it (later). By the way Simon: all your emails land in my Spam folder, no matter how many times I tell click the "Not Spam" button in Gmail. I don't know who's to blame, but it's really only your emails that end up there, so you may want to check that out. Thomas -------------- next part -------------- An HTML attachment was scrubbed... URL: From metaniklas at gmail.com Tue Jun 7 22:24:48 2016 From: metaniklas at gmail.com (Niklas Larsson) Date: Wed, 8 Jun 2016 00:24:48 +0200 Subject: Testsuite total failure on Windows In-Reply-To: References: Message-ID: I get the same spam ranking for Simon's emails. My gmail app says it's because they're from Microsoft but doesn't fill requirements for microsoft.com . Presumably this is because the sender is the list server and not the normal mail server. So it doesn't seem easy to fix. But it would be weird if Gmail is entirely unaware of mailing lists, so maybe there's some way to get one white-listed. Den 7 juni 2016 23:44 skrev "Thomas Miedema" : > Hi Simon, > > Is this you working on my show-stopping problem with the tetssuite? >> sh: line 0: cd: >> c:/users/simonpj/appdata/local/temp/ghctest-qbd2zw123.T9662: No such file >> or directory >> > > I pushed a fix. > > It was my mistake. It turns out there are 2 types of Python on Windows > (msys2 and mingw), and the way they handle paths (and also unicode) is > subtly different. This also explains why you sometimes see validate > failures that others don't (such as T5975a). But now I know the cause, so > we can do something about it (later). > > By the way Simon: all your emails land in my Spam folder, no matter how > many times I tell click the "Not Spam" button in Gmail. I don't know who's > to blame, but it's really only your emails that end up there, so you may > want to check that out. > > Thomas > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Wed Jun 8 04:20:05 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 8 Jun 2016 00:20:05 -0400 Subject: Do we need to maintain PrimRep.VecRep? In-Reply-To: References: <5756DEDA.1050004@apeiron.net> <5756E6D0.9080501@apeiron.net> Message-ID: There's also the question of whether or not the high level simd ops that llvm exposes are the ones that can be easily supported by the native code Gen without duplicating llvm specific logic around lowering on various architectures. Though for the basic horizontal operations that are currently exposed that should be straight forward. But might be more tricky for shuffle and dot product kinds of things. On Tuesday, June 7, 2016, ?mer Sinan A?acan wrote: > Ahh, I see... I finally found the primops, machops, and code generator for > x86: > > MO_V_Insert {} -> needLlvm > MO_V_Extract {} -> needLlvm > MO_V_Add {} -> needLlvm > MO_V_Sub {} -> needLlvm > ... > > > The reason this is not available more widely is lack of support in the > native > > code generator. Do you have any interest in working on adding such > support? > > :) > > I'm afraid I'm short on free time at the moment but I'll let you know if I > have > a chance to work on that. > > Thanks, > Omer > > 2016-06-07 11:22 GMT-04:00 Geoffrey Mainland >: > > Only programs that use vector primops will generate VecRep's. GHC is not > > such a program. > > > > The branch of vector that I modified to use vector primops will generate > > VecRep's. You can find it here: > > > > https://github.com/mainland/vector/tree/simd > > > > It uses a modified version of primitive. See here, for example: > > > > https://github.com/mainland/primitive/blob/simd/Data/Primitive/Multi.hs > > > > The reason this is not available more widely is lack of support in the > > native code generator. Do you have any interest in working on adding > > such support? :) > > > > Cheers, > > Geoff > > > > On 06/07/2016 11:08 AM, ?mer Sinan A?acan wrote: > >> Thanks, I can see the TyCons with VecReps there.. but I still can't see > how the > >> terms are constructed? Can you show me some example programs, or > functions in > >> the compiler, that generate vector terms? (e.g. terms with types with > VecReps) > >> > >> 2016-06-07 10:48 GMT-04:00 Geoffrey Mainland >: > >>> VecRep is used for vector operations. If you aren't using LLVM, you > >>> won't see them. > >>> > >>> VecRep's are generated by utils/genprimopcode/Main.hs. > >>> > >>> Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build > >>> tree---should be plenty of generated VecRep's there :) > >>> > >>> Cheers, > >>> Geoff > >>> > >>> On 06/07/2016 05:00 AM, ?mer Sinan A?acan wrote: > >>>> I have some code that does things depending on PrimReps of terms and > so I have > >>>> to handle VecRep there. To understand what VecRep exactly is and how > to use it I > >>>> looked at its uses, and all I can find was that we have a wired-in > DataCon > >>>> `vecRepDataCon` which has a type that I thought should have VecRep > PrimRep, but > >>>> when I test in GHCi I see that its PrimRep is PtrRep: > >>>> > >>>> ?> map typePrimRep (map dataConRepType (tyConDataCons > runtimeRepTyCon)) > >>>> > [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep] > >>>> > >>>> (This DataCon is not exported and only used in runtimeRepTyCon) > >>>> > >>>> So I think VecRep may not be in use at the moment. Do we still need > to maintain > >>>> it? What's the use case? Can anyone show me a Core term that has a > type whose > >>>> PrimRep is VecRep? > >>>> > >>>> Thanks.. > >>>> _______________________________________________ > >>>> ghc-devs mailing list > >>>> ghc-devs at haskell.org > >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 8 06:04:11 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 8 Jun 2016 06:04:11 +0000 Subject: Windows testsuite improved but still a bug Message-ID: <835a530421da47d4a6fa1b63d6767425@DB4PR30MB030.064d.mgd.msft.net> Thomie Thanks for fixing the testsuite on Windows. I still get some new failures Test framework failures: T10294a (normal) T10420 (normal) T11244 (normal) plugins07 (normal) The log file for one of them is below. Oddly, if I subsequently run a single test make TEST=plugins07 it works fine. Maybe something to do with something not being built? Simon =====> plugins07(normal) 2705 of 5154 [0, 8, 0] cd "c:\users\simonpj\appdata\local\temp\ghctest-pk_7er\test spaces\1\2\3\.\plugins\plugins07" && $MAKE -s --no-print-directory -C rule-defining-plugin package.plugins07 TOP=C:/code/HEAD/testsuite setup.exe: does not exist Makefile:12: recipe for target 'package.plugins07' failed make[3]: *** [package.plugins07] Error 1 *** framework failure for plugins07(normal) pre-command failed: 512 cd "c:\users\simonpj\appdata\local\temp\ghctest-pk_7er\test spaces\1\2\3\.\plugins\plugins07" && $MAKE -s --no-print-directory plugins07 plugins07.run.stdout 2> plugins07.run.stderr Wrong exit code (expected 0 , actual 2 ) Stdout: Makefile:16: recipe for target 'plugins07' failed Stderr: : cannot satisfy -plugin-package rule-defining-plugin (use -v for more information) make[3]: *** [plugins07] Error 1 *** unexpected failure for plugins07(normal) -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 8 06:05:02 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 8 Jun 2016 06:05:02 +0000 Subject: Windows testsuite improved but still a bug Message-ID: <62b58c3954834c8a9b933a2afd40ad77@DB4PR30MB030.064d.mgd.msft.net> PS I should add: this is in a branch I?m working on, not HEAD ? but up to date with HEAD, and I?m doing nothing that will affect plugins From: Simon Peyton Jones Sent: 08 June 2016 07:04 To: 'ghc-devs at haskell.org' Subject: Windows testsuite improved but still a bug Thomie Thanks for fixing the testsuite on Windows. I still get some new failures Test framework failures: T10294a (normal) T10420 (normal) T11244 (normal) plugins07 (normal) The log file for one of them is below. Oddly, if I subsequently run a single test make TEST=plugins07 it works fine. Maybe something to do with something not being built? Simon =====> plugins07(normal) 2705 of 5154 [0, 8, 0] cd "c:\users\simonpj\appdata\local\temp\ghctest-pk_7er\test spaces\1\2\3\.\plugins\plugins07" && $MAKE -s --no-print-directory -C rule-defining-plugin package.plugins07 TOP=C:/code/HEAD/testsuite setup.exe: does not exist Makefile:12: recipe for target 'package.plugins07' failed make[3]: *** [package.plugins07] Error 1 *** framework failure for plugins07(normal) pre-command failed: 512 cd "c:\users\simonpj\appdata\local\temp\ghctest-pk_7er\test spaces\1\2\3\.\plugins\plugins07" && $MAKE -s --no-print-directory plugins07 plugins07.run.stdout 2> plugins07.run.stderr Wrong exit code (expected 0 , actual 2 ) Stdout: Makefile:16: recipe for target 'plugins07' failed Stderr: : cannot satisfy -plugin-package rule-defining-plugin (use -v for more information) make[3]: *** [plugins07] Error 1 *** unexpected failure for plugins07(normal) -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Wed Jun 8 08:19:12 2016 From: rwbarton at gmail.com (Reid Barton) Date: Wed, 8 Jun 2016 04:19:12 -0400 Subject: Why upper bound version numbers? In-Reply-To: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> Message-ID: On Tue, Jun 7, 2016 at 9:31 AM, Ben Lippmeier wrote: > > > On 7 Jun 2016, at 7:02 am, Dominick Samperi wrote: > > > > Why would a package developer want to upper bound the version number > > for packages like base? For example, the clash package requires > > > > base >= 4.2 && base <= 4.3 > > I put an upper bound on all my libraries as a proxy for the GHC version. > Each time a new GHC version is released sometimes my libraries work with it > and sometimes not. I remember a ?burning bridges? event in recent history, > when the definition of the Monad class changed and broke a lot of things. > > Suppose you maintain a library that is used by a lot of first year uni > students (like gloss). Suppose the next GHC version comes around and your > library hasn?t been updated yet because you?re waiting on some dependencies > to get fixed before you can release your own. Do you want your students to > get a ?cannot install on this version? error, or some confusing build error > which they don?t understand? > This is a popular but ultimately silly argument. First, cabal dependency solver error messages are terrible; there's no way a new user would figure out from a bunch of solver output about things like "base-4.7.0.2" and "Dependency tree exhaustively searched" that the solution is to build with an older version of GHC. A configuration error and a build error will both send the same message: "something is broken". Second, this argument ignores the much more likely case that the package would have just worked with the new GHC, but the upper bound results in an unnecessary (and again, terrible) error message and a bad user experience. The best case is that the user somehow learns about --allow-newer=base, but cabal's error message doesn't even suggest trying this and it's still an unnecessary hoop to jump through. Experienced users are also only harmed by these upper bounds, since it's generally obvious when a program fails to build due to a change in base and the normal reaction to a version error with base is just to retry with --allow-newer=base anyways. Of course the best thing is to stick to the part of the language that is unlikely to be broken by future versions of base; sadly this seems to be impossible in the current climate... Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From benl at ouroborus.net Wed Jun 8 08:31:08 2016 From: benl at ouroborus.net (Ben Lippmeier) Date: Wed, 8 Jun 2016 18:31:08 +1000 Subject: Why upper bound version numbers? In-Reply-To: References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> Message-ID: <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> > On 8 Jun 2016, at 6:19 pm, Reid Barton wrote: > > Suppose you maintain a library that is used by a lot of first year uni students (like gloss). Suppose the next GHC version comes around and your library hasn?t been updated yet because you?re waiting on some dependencies to get fixed before you can release your own. Do you want your students to get a ?cannot install on this version? error, or some confusing build error which they don?t understand? > > This is a popular but ultimately silly argument. First, cabal dependency solver error messages are terrible; there's no way a new user would figure out from a bunch of solver output about things like "base-4.7.0.2" and "Dependency tree exhaustively searched" that the solution is to build with an older version of GHC. :-) At least ?Dependency tree exhaustively searched? sounds like it?s not the maintainer?s problem. I prefer the complaints to say ?can you please bump the bounds on this package? rather than ?your package is broken?. Ben. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Wed Jun 8 08:38:50 2016 From: rwbarton at gmail.com (Reid Barton) Date: Wed, 8 Jun 2016 04:38:50 -0400 Subject: Linux (ELF) Support for "ghc -static -shared" In-Reply-To: References: Message-ID: On Sat, Jun 4, 2016 at 1:48 AM, Travis Whitaker wrote: > Suppose I have some module Foo with foreign exports. On some platforms I > can do something like: > > ghc -static -shared Foo.o ... > > The resulting shared library would have the base libraries and the RTS > statically linked in. From what I understand this is possible on BSDs > because generating PIC is the default there (for making PIEs I'd imagine), > and possible on Windows because the dynamic loading process involves some > technique that doesn't require PIC. On Linux (at least x86_64) this doesn't > work by default since libHSbase, libHSrts et al. are not built with -fPIC > unless one specifically asks for it when building GHC. As far as I know > this is the only way to get -static -shared to work on this platform. > I believe that's all correct. Incidentally there was just a related post on reddit yesterday: https://www.reddit.com/r/haskell/comments/4my2cn/a_story_of_how_i_built_static_haskell_libraries/ > While the use cases for such stand-alone shared libraries might be small > niches, I was curious whether or not there was any discussion about > potential strategies for making it easier to build them for Linux. At the > very least, perhaps a single switch for the configure script or build.mk > to make it easier to build GHC+libs with -fPIC on Linux. > That's certainly a good idea. Mind filing a ticket? Another step up might be providing *_PIC.a objects for the base libraries, > so that the non-PIC objects are still available for the majority of cases > in which PIC is not required. > I think we don't do this mainly because it would inflate the size of the binary distribution significantly for something that is, as you say, rather a niche use case. Regards, Reid Barton -------------- next part -------------- An HTML attachment was scrubbed... URL: From mgsloan at gmail.com Wed Jun 8 20:01:25 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 8 Jun 2016 13:01:25 -0700 Subject: Why upper bound version numbers? In-Reply-To: <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> Message-ID: Right, part of the issue with having dependency solving at the core of your workflow is that you never really know who's to blame. When running into this circumstance, either: 1) Some maintainer made a mistake. 2) Some maintainer did not have perfect knowledge of the future and has not yet updated some upper bounds. Or, upper bounds didn't get retroactively bumped (usual). 3) You're asking cabal to do something that can't be done. 4) There's a bug in the solver. So the only thing to do is to say "something went wrong". In a way it is similar to type inference, it is difficult to give specific, concrete error messages without making some arbitrary choices about which constraints have gotten pushed around. I think upper bounds could potentially be made viable by having both hard and soft constraints. Until then, people are putting 2 meanings into one thing. By having the distinction, I think cabal-install could provide much better errors than it does currently. This has come up before, I'm not sure what came of those discussions. My thoughts on how this would work: * The dependency solver would prioritize hard constraints, and tell you which soft constraints need to be lifted. I believe the solver even already has this. Stack's integration with the solver will actually first try to get a plan that doesn't override any snapshot versions, by specifying them as hard constraints. If that doesn't work, it tries again with soft constraints. * "--allow-soft" or something would ignore soft constraints. Ideally this would be selective on a per package / upper vs lower. * It may be worth having the default be "--allow-soft" + be noisy about which constraints got ignored. Then, you could have a "--pedantic-bounds" flag that forces following soft bounds. I could get behind upper bounds if they allowed maintainers to actually communicate their intention, and if we had good automation for their maintenance. As is, putting upper bounds on everything seems to cause more problems than it solves. -Michael On Wed, Jun 8, 2016 at 1:31 AM, Ben Lippmeier wrote: > > On 8 Jun 2016, at 6:19 pm, Reid Barton wrote: > > Suppose you maintain a library that is used by a lot of first year uni >> students (like gloss). Suppose the next GHC version comes around and your >> library hasn?t been updated yet because you?re waiting on some dependencies >> to get fixed before you can release your own. Do you want your students to >> get a ?cannot install on this version? error, or some confusing build error >> which they don?t understand? >> > > This is a popular but ultimately silly argument. First, cabal dependency > solver error messages are terrible; there's no way a new user would figure > out from a bunch of solver output about things like "base-4.7.0.2" and > "Dependency tree exhaustively searched" that the solution is to build with > an older version of GHC. > > > :-) At least ?Dependency tree exhaustively searched? sounds like it?s not > the maintainer?s problem. I prefer the complaints to say ?can you please > bump the bounds on this package? rather than ?your package is broken?. > > Ben. > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Thu Jun 9 07:14:53 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Thu, 09 Jun 2016 00:14:53 -0700 Subject: Call for talks: Haskell Implementors Workshop 2016, Aug 24, Nara Message-ID: <1465456335-sup-6629@sabre> Call for Contributions ACM SIGPLAN Haskell Implementors' Workshop http://haskell.org/haskellwiki/HaskellImplementorsWorkshop/2016 Nara, Japan, 24 September, 2016 Co-located with ICFP 2016 http://www.icfpconference.org/icfp2016/ Important dates --------------- Proposal Deadline: Monday, 8 August, 2016 Notification: Monday, 22 August, 2016 Workshop: Saturday, 24 September, 2016 The 8th Haskell Implementors' Workshop is to be held alongside ICFP 2016 this year in Nara. It is a forum for people involved in the design and development of Haskell implementations, tools, libraries, and supporting infrastructure, to share their work and discuss future directions and collaborations with others. Talks and/or demos are proposed by submitting an abstract, and selected by a small program committee. There will be no published proceedings; the workshop will be informal and interactive, with a flexible timetable and plenty of room for ad-hoc discussion, demos, and impromptu short talks. Scope and target audience ------------------------- It is important to distinguish the Haskell Implementors' Workshop from the Haskell Symposium which is also co-located with ICFP 2016. The Haskell Symposium is for the publication of Haskell-related research. In contrast, the Haskell Implementors' Workshop will have no proceedings -- although we will aim to make talk videos, slides and presented data available with the consent of the speakers. In the Haskell Implementors' Workshop, we hope to study the underlying technology. We want to bring together anyone interested in the nitty-gritty details behind turning plain-text source code into a deployed product. Having said that, members of the wider Haskell community are more than welcome to attend the workshop -- we need your feedback to keep the Haskell ecosystem thriving. The scope covers any of the following topics. There may be some topics that people feel we've missed, so by all means submit a proposal even if it doesn't fit exactly into one of these buckets: * Compilation techniques * Language features and extensions * Type system implementation * Concurrency and parallelism: language design and implementation * Performance, optimisation and benchmarking * Virtual machines and run-time systems * Libraries and tools for development or deployment Talks ----- At this stage we would like to invite proposals from potential speakers for talks and demonstrations. We are aiming for 20 minute talks with 10 minutes for questions and changeovers. We want to hear from people writing compilers, tools, or libraries, people with cool ideas for directions in which we should take the platform, proposals for new features to be implemented, and half-baked crazy ideas. Please submit a talk title and abstract of no more than 300 words. Submissions should be made via HotCRP. The website is: https://icfp-hiw16.hotcrp.com/ We will also have a lightning talks session which will be organised on the day. These talks will be 5-10 minutes, depending on available time. Suggested topics for lightning talks are to present a single idea, a work-in-progress project, a problem to intrigue and perplex Haskell implementors, or simply to ask for feedback and collaborators. Organisers ---------- * Joachim Breitner (Karlsruhe Institut f?r Technologie) * Duncan Coutts (Well Typed) * Michael Snoyman (FP Complete) * Luite Stegeman (ghcjs) * Niki Vazou (UCSD) * Stephanie Weirich (University of Pennsylvania) * Edward Z. Yang - chair (Stanford University) From ezyang at mit.edu Thu Jun 9 07:17:18 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Thu, 09 Jun 2016 00:17:18 -0700 Subject: Call for talks: Haskell Implementors Workshop 2016, Sep 24 (FIXED), Nara Message-ID: <1465456550-sup-6234@sabre> (...and now with the right date in the subject line!) Call for Contributions ACM SIGPLAN Haskell Implementors' Workshop http://haskell.org/haskellwiki/HaskellImplementorsWorkshop/2016 Nara, Japan, 24 September, 2016 Co-located with ICFP 2016 http://www.icfpconference.org/icfp2016/ Important dates --------------- Proposal Deadline: Monday, 8 August, 2016 Notification: Monday, 22 August, 2016 Workshop: Saturday, 24 September, 2016 The 8th Haskell Implementors' Workshop is to be held alongside ICFP 2016 this year in Nara. It is a forum for people involved in the design and development of Haskell implementations, tools, libraries, and supporting infrastructure, to share their work and discuss future directions and collaborations with others. Talks and/or demos are proposed by submitting an abstract, and selected by a small program committee. There will be no published proceedings; the workshop will be informal and interactive, with a flexible timetable and plenty of room for ad-hoc discussion, demos, and impromptu short talks. Scope and target audience ------------------------- It is important to distinguish the Haskell Implementors' Workshop from the Haskell Symposium which is also co-located with ICFP 2016. The Haskell Symposium is for the publication of Haskell-related research. In contrast, the Haskell Implementors' Workshop will have no proceedings -- although we will aim to make talk videos, slides and presented data available with the consent of the speakers. In the Haskell Implementors' Workshop, we hope to study the underlying technology. We want to bring together anyone interested in the nitty-gritty details behind turning plain-text source code into a deployed product. Having said that, members of the wider Haskell community are more than welcome to attend the workshop -- we need your feedback to keep the Haskell ecosystem thriving. The scope covers any of the following topics. There may be some topics that people feel we've missed, so by all means submit a proposal even if it doesn't fit exactly into one of these buckets: * Compilation techniques * Language features and extensions * Type system implementation * Concurrency and parallelism: language design and implementation * Performance, optimisation and benchmarking * Virtual machines and run-time systems * Libraries and tools for development or deployment Talks ----- At this stage we would like to invite proposals from potential speakers for talks and demonstrations. We are aiming for 20 minute talks with 10 minutes for questions and changeovers. We want to hear from people writing compilers, tools, or libraries, people with cool ideas for directions in which we should take the platform, proposals for new features to be implemented, and half-baked crazy ideas. Please submit a talk title and abstract of no more than 300 words. Submissions should be made via HotCRP. The website is: https://icfp-hiw16.hotcrp.com/ We will also have a lightning talks session which will be organised on the day. These talks will be 5-10 minutes, depending on available time. Suggested topics for lightning talks are to present a single idea, a work-in-progress project, a problem to intrigue and perplex Haskell implementors, or simply to ask for feedback and collaborators. Organisers ---------- * Joachim Breitner (Karlsruhe Institut f?r Technologie) * Duncan Coutts (Well Typed) * Michael Snoyman (FP Complete) * Luite Stegeman (ghcjs) * Niki Vazou (UCSD) * Stephanie Weirich (University of Pennsylvania) * Edward Z. Yang - chair (Stanford University) From hesselink at gmail.com Thu Jun 9 08:01:54 2016 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 9 Jun 2016 10:01:54 +0200 Subject: Why upper bound version numbers? In-Reply-To: References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> Message-ID: What do you expect will be the distribution of 'soft' and 'hard' upper bounds? In my experience, all upper bounds currently are 'soft' upper bounds. They might become 'hard' upper bounds for a short while after e.g. a GHC release, but in general, if a package maintainer knows that a package fails to work with a certain version of a dependency, they fix it. So it seems to me that this is not so much a choice between 'soft' and 'hard' upper bounds, but a choice on what to do when you can't resolve dependencies in the presence of the current (upper) bounds. Currently, as you say, we give pretty bad error messages. The alternative you propose (just try) currently often gives the same result in my experience: bad error messages, in this case not from the solver, but unintelligible compiler errors in an unknown package. So it seems the solution might just be one of messaging: make the initial resolver error much friendlier, and give a suggestion to use e.g. --allow-newer=foo. The opposite might also be interesting to explore: if installing a dependency (so not something you're developing or explicitly asking for) fails to install and doesn't have an upper bound, suggest something like --constaint=foo wrote: > Right, part of the issue with having dependency solving at the core of your > workflow is that you never really know who's to blame. When running into > this circumstance, either: > > 1) Some maintainer made a mistake. > 2) Some maintainer did not have perfect knowledge of the future and has not > yet updated some upper bounds. Or, upper bounds didn't get retroactively > bumped (usual). > 3) You're asking cabal to do something that can't be done. > 4) There's a bug in the solver. > > So the only thing to do is to say "something went wrong". In a way it is > similar to type inference, it is difficult to give specific, concrete error > messages without making some arbitrary choices about which constraints have > gotten pushed around. > > I think upper bounds could potentially be made viable by having both hard > and soft constraints. Until then, people are putting 2 meanings into one > thing. By having the distinction, I think cabal-install could provide much > better errors than it does currently. This has come up before, I'm not sure > what came of those discussions. My thoughts on how this would work: > > * The dependency solver would prioritize hard constraints, and tell you > which soft constraints need to be lifted. I believe the solver even already > has this. Stack's integration with the solver will actually first try to > get a plan that doesn't override any snapshot versions, by specifying them > as hard constraints. If that doesn't work, it tries again with soft > constraints. > > * "--allow-soft" or something would ignore soft constraints. Ideally this > would be selective on a per package / upper vs lower. > > * It may be worth having the default be "--allow-soft" + be noisy about > which constraints got ignored. Then, you could have a "--pedantic-bounds" > flag that forces following soft bounds. > > I could get behind upper bounds if they allowed maintainers to actually > communicate their intention, and if we had good automation for their > maintenance. As is, putting upper bounds on everything seems to cause more > problems than it solves. > > -Michael > > On Wed, Jun 8, 2016 at 1:31 AM, Ben Lippmeier wrote: >> >> >> On 8 Jun 2016, at 6:19 pm, Reid Barton wrote: >> >>> Suppose you maintain a library that is used by a lot of first year uni >>> students (like gloss). Suppose the next GHC version comes around and your >>> library hasn?t been updated yet because you?re waiting on some dependencies >>> to get fixed before you can release your own. Do you want your students to >>> get a ?cannot install on this version? error, or some confusing build error >>> which they don?t understand? >> >> >> This is a popular but ultimately silly argument. First, cabal dependency >> solver error messages are terrible; there's no way a new user would figure >> out from a bunch of solver output about things like "base-4.7.0.2" and >> "Dependency tree exhaustively searched" that the solution is to build with >> an older version of GHC. >> >> >> :-) At least ?Dependency tree exhaustively searched? sounds like it?s not >> the maintainer?s problem. I prefer the complaints to say ?can you please >> bump the bounds on this package? rather than ?your package is broken?. >> >> Ben. >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From alan.zimm at gmail.com Thu Jun 9 08:07:53 2016 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Thu, 9 Jun 2016 10:07:53 +0200 Subject: Why upper bound version numbers? In-Reply-To: References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> Message-ID: I think "hard" upper bounds would come about in situations where a new version of a dependency is released that breaks things in a package, so until the breakage is fixed a hard upper bound is required. Likewise for hard lower bounds. And arguments about "it shouldn't happen with the PVP" don't hold, because it does happen, PVP is a human judgement thing. Alan On Thu, Jun 9, 2016 at 10:01 AM, Erik Hesselink wrote: > What do you expect will be the distribution of 'soft' and 'hard' upper > bounds? In my experience, all upper bounds currently are 'soft' upper > bounds. They might become 'hard' upper bounds for a short while after > e.g. a GHC release, but in general, if a package maintainer knows that > a package fails to work with a certain version of a dependency, they > fix it. > > So it seems to me that this is not so much a choice between 'soft' and > 'hard' upper bounds, but a choice on what to do when you can't resolve > dependencies in the presence of the current (upper) bounds. Currently, > as you say, we give pretty bad error messages. The alternative you > propose (just try) currently often gives the same result in my > experience: bad error messages, in this case not from the solver, but > unintelligible compiler errors in an unknown package. So it seems the > solution might just be one of messaging: make the initial resolver > error much friendlier, and give a suggestion to use e.g. > --allow-newer=foo. The opposite might also be interesting to explore: > if installing a dependency (so not something you're developing or > explicitly asking for) fails to install and doesn't have an upper > bound, suggest something like --constaint=foo > Do you have different experiences regarding the number of 'hard' upper > bounds that exist? > > Regards, > > Erik > > On 8 June 2016 at 22:01, Michael Sloan wrote: > > Right, part of the issue with having dependency solving at the core of > your > > workflow is that you never really know who's to blame. When running into > > this circumstance, either: > > > > 1) Some maintainer made a mistake. > > 2) Some maintainer did not have perfect knowledge of the future and has > not > > yet updated some upper bounds. Or, upper bounds didn't get retroactively > > bumped (usual). > > 3) You're asking cabal to do something that can't be done. > > 4) There's a bug in the solver. > > > > So the only thing to do is to say "something went wrong". In a way it is > > similar to type inference, it is difficult to give specific, concrete > error > > messages without making some arbitrary choices about which constraints > have > > gotten pushed around. > > > > I think upper bounds could potentially be made viable by having both hard > > and soft constraints. Until then, people are putting 2 meanings into one > > thing. By having the distinction, I think cabal-install could provide > much > > better errors than it does currently. This has come up before, I'm not > sure > > what came of those discussions. My thoughts on how this would work: > > > > * The dependency solver would prioritize hard constraints, and tell you > > which soft constraints need to be lifted. I believe the solver even > already > > has this. Stack's integration with the solver will actually first try to > > get a plan that doesn't override any snapshot versions, by specifying > them > > as hard constraints. If that doesn't work, it tries again with soft > > constraints. > > > > * "--allow-soft" or something would ignore soft constraints. Ideally > this > > would be selective on a per package / upper vs lower. > > > > * It may be worth having the default be "--allow-soft" + be noisy about > > which constraints got ignored. Then, you could have a > "--pedantic-bounds" > > flag that forces following soft bounds. > > > > I could get behind upper bounds if they allowed maintainers to actually > > communicate their intention, and if we had good automation for their > > maintenance. As is, putting upper bounds on everything seems to cause > more > > problems than it solves. > > > > -Michael > > > > On Wed, Jun 8, 2016 at 1:31 AM, Ben Lippmeier > wrote: > >> > >> > >> On 8 Jun 2016, at 6:19 pm, Reid Barton wrote: > >> > >>> Suppose you maintain a library that is used by a lot of first year uni > >>> students (like gloss). Suppose the next GHC version comes around and > your > >>> library hasn?t been updated yet because you?re waiting on some > dependencies > >>> to get fixed before you can release your own. Do you want your > students to > >>> get a ?cannot install on this version? error, or some confusing build > error > >>> which they don?t understand? > >> > >> > >> This is a popular but ultimately silly argument. First, cabal dependency > >> solver error messages are terrible; there's no way a new user would > figure > >> out from a bunch of solver output about things like "base-4.7.0.2" and > >> "Dependency tree exhaustively searched" that the solution is to build > with > >> an older version of GHC. > >> > >> > >> :-) At least ?Dependency tree exhaustively searched? sounds like it?s > not > >> the maintainer?s problem. I prefer the complaints to say ?can you please > >> bump the bounds on this package? rather than ?your package is broken?. > >> > >> Ben. > >> > >> > >> _______________________________________________ > >> ghc-devs mailing list > >> ghc-devs at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > >> > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Thu Jun 9 08:18:44 2016 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 9 Jun 2016 10:18:44 +0200 Subject: Why upper bound version numbers? In-Reply-To: References: <60F7B2CB-15FD-44B1-8F7E-890FEAF9365A@ouroborus.net> <5F158D89-57F4-4BE2-906A-87BB767B1C3B@ouroborus.net> Message-ID: Sure, I'm just wondering about how this plays out in reality: of people getting unsolvable plans, how many are due to hard upper bounds and how many due to soft upper bounds? We can't reliably tell, of course, since we don't have this distinction currently, but I was trying to get some anecdotal data to add to my own. Erik On 9 June 2016 at 10:07, Alan & Kim Zimmerman wrote: > I think "hard" upper bounds would come about in situations where a new > version of a dependency is released that breaks things in a package, so > until the breakage is fixed a hard upper bound is required. Likewise for > hard lower bounds. > > And arguments about "it shouldn't happen with the PVP" don't hold, because > it does happen, PVP is a human judgement thing. > > Alan > > > On Thu, Jun 9, 2016 at 10:01 AM, Erik Hesselink wrote: >> >> What do you expect will be the distribution of 'soft' and 'hard' upper >> bounds? In my experience, all upper bounds currently are 'soft' upper >> bounds. They might become 'hard' upper bounds for a short while after >> e.g. a GHC release, but in general, if a package maintainer knows that >> a package fails to work with a certain version of a dependency, they >> fix it. >> >> So it seems to me that this is not so much a choice between 'soft' and >> 'hard' upper bounds, but a choice on what to do when you can't resolve >> dependencies in the presence of the current (upper) bounds. Currently, >> as you say, we give pretty bad error messages. The alternative you >> propose (just try) currently often gives the same result in my >> experience: bad error messages, in this case not from the solver, but >> unintelligible compiler errors in an unknown package. So it seems the >> solution might just be one of messaging: make the initial resolver >> error much friendlier, and give a suggestion to use e.g. >> --allow-newer=foo. The opposite might also be interesting to explore: >> if installing a dependency (so not something you're developing or >> explicitly asking for) fails to install and doesn't have an upper >> bound, suggest something like --constaint=foo> >> Do you have different experiences regarding the number of 'hard' upper >> bounds that exist? >> >> Regards, >> >> Erik >> >> On 8 June 2016 at 22:01, Michael Sloan wrote: >> > Right, part of the issue with having dependency solving at the core of >> > your >> > workflow is that you never really know who's to blame. When running >> > into >> > this circumstance, either: >> > >> > 1) Some maintainer made a mistake. >> > 2) Some maintainer did not have perfect knowledge of the future and has >> > not >> > yet updated some upper bounds. Or, upper bounds didn't get >> > retroactively >> > bumped (usual). >> > 3) You're asking cabal to do something that can't be done. >> > 4) There's a bug in the solver. >> > >> > So the only thing to do is to say "something went wrong". In a way it >> > is >> > similar to type inference, it is difficult to give specific, concrete >> > error >> > messages without making some arbitrary choices about which constraints >> > have >> > gotten pushed around. >> > >> > I think upper bounds could potentially be made viable by having both >> > hard >> > and soft constraints. Until then, people are putting 2 meanings into >> > one >> > thing. By having the distinction, I think cabal-install could provide >> > much >> > better errors than it does currently. This has come up before, I'm not >> > sure >> > what came of those discussions. My thoughts on how this would work: >> > >> > * The dependency solver would prioritize hard constraints, and tell you >> > which soft constraints need to be lifted. I believe the solver even >> > already >> > has this. Stack's integration with the solver will actually first try >> > to >> > get a plan that doesn't override any snapshot versions, by specifying >> > them >> > as hard constraints. If that doesn't work, it tries again with soft >> > constraints. >> > >> > * "--allow-soft" or something would ignore soft constraints. Ideally >> > this >> > would be selective on a per package / upper vs lower. >> > >> > * It may be worth having the default be "--allow-soft" + be noisy about >> > which constraints got ignored. Then, you could have a >> > "--pedantic-bounds" >> > flag that forces following soft bounds. >> > >> > I could get behind upper bounds if they allowed maintainers to actually >> > communicate their intention, and if we had good automation for their >> > maintenance. As is, putting upper bounds on everything seems to cause >> > more >> > problems than it solves. >> > >> > -Michael >> > >> > On Wed, Jun 8, 2016 at 1:31 AM, Ben Lippmeier >> > wrote: >> >> >> >> >> >> On 8 Jun 2016, at 6:19 pm, Reid Barton wrote: >> >> >> >>> Suppose you maintain a library that is used by a lot of first year >> >>> uni >> >>> students (like gloss). Suppose the next GHC version comes around and >> >>> your >> >>> library hasn?t been updated yet because you?re waiting on some >> >>> dependencies >> >>> to get fixed before you can release your own. Do you want your >> >>> students to >> >>> get a ?cannot install on this version? error, or some confusing build >> >>> error >> >>> which they don?t understand? >> >> >> >> >> >> This is a popular but ultimately silly argument. First, cabal >> >> dependency >> >> solver error messages are terrible; there's no way a new user would >> >> figure >> >> out from a bunch of solver output about things like "base-4.7.0.2" and >> >> "Dependency tree exhaustively searched" that the solution is to build >> >> with >> >> an older version of GHC. >> >> >> >> >> >> :-) At least ?Dependency tree exhaustively searched? sounds like it?s >> >> not >> >> the maintainer?s problem. I prefer the complaints to say ?can you >> >> please >> >> bump the bounds on this package? rather than ?your package is broken?. >> >> >> >> Ben. >> >> >> >> >> >> _______________________________________________ >> >> ghc-devs mailing list >> >> ghc-devs at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> >> > >> > >> > _______________________________________________ >> > ghc-devs mailing list >> > ghc-devs at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > From voldermort at hotmail.com Thu Jun 9 09:22:23 2016 From: voldermort at hotmail.com (Jeremy .) Date: Thu, 9 Jun 2016 09:22:23 +0000 Subject: Why upper bound version numbers? Message-ID: Versions of package dependencies can be categorised into 5 sets: D1) Versions which the maintainer has tested and found to work D2) Versions which the maintainer has not tested but expects to work D3) Versions which the maintainer has tested and found to not work D4) Versions which the maintainer has not tested but expects to not work D5) Everything else Cabal, however, only knows of 3 sets: C1) Versions which satisfy build-depends C2) Versions which satisfy build-depends with --allow-newer C3) Everything else The problem arises from the fact that the D sets to not map well onto the C sets, even after combining D1&D2 and D3&D4. Perhaps this could be solved with a new .cabal property, breaks-with. The solver will then prefer packages in this order: 1) Versions that satisfy build-depends 2) Versions that are not in breaks-with, unless a flag such as --strict-build-depends is applied This may also lead to clearer build-depends, as instead of multiple ranges with gaps to skip know broken versions, build-depends can list a single range, and breaks-with can list the bad versions. From oleg.grenrus at iki.fi Thu Jun 9 11:28:20 2016 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Thu, 9 Jun 2016 14:28:20 +0300 Subject: Why upper bound version numbers? In-Reply-To: References: Message-ID: <7EDFE4E3-4DBF-4012-906F-7ADB46CA2E7E@iki.fi> My five cents: There is discussion/work in Cabal dev about splitting the solver out. [1] I hope that at the end, there will be functionality that you can construct build/install plan by whatever means and use cabal functionality to execute it. Another functionality brought by work on haskell-security is that 01-index.tar.gz is append only file, so it?s ?easy? to travel back in time in Hackage history. Combining those one can run an experiment, on how much - existing upper bounds prevent cabal from finding working install-plan; and how this change over time, because of maintainers activity. - non-existing upper bounds prevent found install-plan to compile properly; and how this change over time, because of a) maintainers own activity, b) Hackage trustee activity - other stats Until quantitative report justifying that upper bounds are clearly bad-idea, I would not propose any dramatical changes to how default solver works or Cabal-definition-format spec. With own solvers it would be easy to experiment and provide own metadata. As Hackage Trustee I do see much more full-of-red (failed builds) matrices on matrix.h.h.o than dark green ones (no install plan). Unfortunately only my gut feeling, no hard numbers but, but GHC <7.4/7.6 tends to be often red (because of base ==4.*, or base <5), or there are full lines of red because newer version of dependency causes breakage (which is no upper-bounds) For example. fast-logger introduced new type alias and new functionality in System.Log.FastLogger in minor version 2.4.4 [3]: --- Diff for | 2.4.3 ? 2.4.4 | --- + System.Log.FastLogger.Date + type FormattedTime = ByteString + type TimeFormat = ByteString + newTimeCache :: TimeFormat -> IO (IO FormattedTime) + simpleTimeFormat :: TimeFormat + simpleTimeFormat' :: TimeFormat ? System.Log.FastLogger + type FastLogger = LogStr -> IO () + LogCallback :: (LogStr -> IO ()) -> (IO ()) -> LogType + LogFile :: FilePath -> BufSize -> LogType + LogFileAutoRotate :: FileLogSpec -> BufSize -> LogType + LogNone :: LogType + LogStderr :: BufSize -> LogType + LogStdout :: BufSize -> LogType + data LogType + type TimedFastLogger = (FormattedTime -> LogStr) -> IO () + newFastLogger :: LogType -> IO (FastLogger, IO ()) + newTimedFastLogger :: (IO FormattedTime) -> LogType -> IO (TimedFastLogger, IO ()) + withFastLogger :: LogType -> (FastLogger -> IO a) -> IO () + withTimedFastLogger :: (IO FormattedTime) -> LogType -> (TimedFastLogger -> IO a) -> IO () ? System.Log.FastLogger.File ? New: check :: FilePath -> IO () Old: check :: FileLogSpec -> IO () [+ Added] [- Removed] [? Modified] [? Unmodified] And according to PVP you can do it, bumping only minor version. (The change in System.Log.FastLogger.File is breaking change, so it should been major bump, but our example holds even it was 2.4.4 -> 2.5) wai-logger package depends on fast-logger, and broke after new fast-logger release [4] because of: - doesn?t have upper-bounds - import(ed) modules improperly [5] The new version was fixed immediately, so I suspect that whetever the issue were about breakage or restrictive-upper bounds (pinged from Stackage) it would been fixed as fast. Yet now there is still lot?s of red in the matrix [6]. It?s highly unlikely that old versions would be picked by solver, but not impossible, happened to me, ekg-json picked very old aeson version (well again, no bounds there!) and broke. [7] To summarise this example, I?d rather make PRs to relax version bounds, then try to guess what bounds I have to adjust so I get working install plan. And to conclude, - Please setup CI, e.g. using Herbert?s script [8]. It?s very easy! - Have the base bounds restricting GHC?s to ones you test. - Contributing (i.e. to bump version bounds) would be extremely easy for others and you. Herbert is also very fast to make packages for newer (even unreleased version of GHC), so we had ability to test and fix! many packages before GHC-8.0 was officially released making adaptations as early as this year?s January. - Oleg - [1]: https://github.com/haskell/cabal/pull/3222 - [2]: http://matrix.hackage.haskell.org/packages see red-alert tag - [3]: http://hackage.haskell.org/package/fast-logger-2.4.4/docs/System-Log-FastLogger.html - [4]: https://github.com/kazu-yamamoto/logger/issues/88 - [5]: https://wiki.haskell.org/Import_modules_properly - [6]: http://imgur.com/bTYI8KC - [7] https://github.com/tibbe/ekg-json/pull/3 - [8] https://github.com/hvr/multi-ghc-travis > On 09 Jun 2016, at 12:22, Jeremy . wrote: > > Versions of package dependencies can be categorised into 5 sets: > > D1) Versions which the maintainer has tested and found to work > D2) Versions which the maintainer has not tested but expects to work > D3) Versions which the maintainer has tested and found to not work > D4) Versions which the maintainer has not tested but expects to not work > D5) Everything else > > Cabal, however, only knows of 3 sets: > > C1) Versions which satisfy build-depends > C2) Versions which satisfy build-depends with --allow-newer > C3) Everything else > > The problem arises from the fact that the D sets to not map well onto the C sets, even after combining D1&D2 and D3&D4. Perhaps this could be solved with a new .cabal property, breaks-with. The solver will then prefer packages in this order: > > 1) Versions that satisfy build-depends > 2) Versions that are not in breaks-with, unless a flag such as --strict-build-depends is applied > > This may also lead to clearer build-depends, as instead of multiple ranges with gaps to skip know broken versions, build-depends can list a single range, and breaks-with can list the bad versions. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From ben at well-typed.com Thu Jun 9 16:52:01 2016 From: ben at well-typed.com (Ben Gamari) Date: Thu, 09 Jun 2016 18:52:01 +0200 Subject: Harbourmaster is still not building diffs In-Reply-To: References: Message-ID: <87k2hy71am.fsf@smart-cactus.org> Matthew Pickering writes: > Since a couple of months ago, harbourmaster no longer builds diffs. > This is quite a large barrier to entry for new contributors as running > ./validate takes a long time. Hi Matthew, Indeed it has been a very long time since Harbormaster has built diffs. The story is this: in the past our Harbormaster infrastructure has been rather brittle due to its reliance on `arc` to apply differentials. With recently work in Phabricator this fragility can now be addressed, but at the cost of reworking some of our existing build infrastructure. Moreover, the new Harbormaster story seems to not have been designed with a public project such as ours in mind, so there are a few security issues which need to be worked out (namely it requires a git repository to which all Phab users can push commits). Getting to this point has unfortunately taken significantly longer than expected to get to this point and it's still not entirely clear how the new Harbormaster roll-out will work. At this point I suspect we ought to just roll back to the previous Harbormaster automation script unless there is a clear path forward with the new infrastructure. Austin, what do you think? Can we set a concrete timeline for bringing Harbormaster back up? Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From dsf at seereason.com Thu Jun 9 17:43:42 2016 From: dsf at seereason.com (David Fox) Date: Thu, 9 Jun 2016 10:43:42 -0700 Subject: Why upper bound version numbers? In-Reply-To: <878tyhplsn.fsf@gmail.com> References: <878tyhplsn.fsf@gmail.com> Message-ID: On Mon, Jun 6, 2016 at 11:15 PM, Herbert Valerio Riedel wrote: > or even worse silent failures where the code behaves > subtly wrong or different than expected. Testsuites mitigate this to > some degree, but they too are an imperfect solution to this hard > problem. > ?It seems to me that if you have any thought at all for your library's clients the chances of this happening are pretty insignificant. -------------- next part -------------- An HTML attachment was scrubbed... URL: From howard_b_golden at yahoo.com Thu Jun 9 19:12:24 2016 From: howard_b_golden at yahoo.com (Howard B. Golden) Date: Thu, 9 Jun 2016 19:12:24 +0000 (UTC) Subject: Why upper bound version numbers? In-Reply-To: References: <878tyhplsn.fsf@gmail.com> Message-ID: <742202034.431489.1465499544788.JavaMail.yahoo@mail.yahoo.com> On June 9, 2016 10:43:00 -0700 David Fox wrote: ?> It seems to me that if you have any thought at all for your library's > clients the chances of this happening are pretty insignificant. Sadly (IMO), this happens all too frequently. Upward compatibility suffers because most package authors are (naturally) interested in solving their own problems, and they don't get paid to think about others using their package who might be affected by an upward-incompatible change. This is a hard problem to solve unless we can find a way to pay package authors to take the extra time and effort to satisfy their users. Most open source communities are stricter about requiring upward compatibility than the Haskell community is. Howard ________________________________ From: David Fox To: Herbert Valerio Riedel Cc: "ghc-devs at haskell.org" Sent: Thursday, June 9, 2016 10:43 AM Subject: Re: Why upper bound version numbers? On Mon, Jun 6, 2016 at 11:15 PM, Herbert Valerio Riedel wrote: or even worse silent failures where the code behaves >subtly wrong or different than expected. Testsuites mitigate this to >some degree, but they too are an imperfect solution to this hard >problem. > ?It seems to me that if you have any thought at all for your library's clients the chances of this happening are pretty insignificant. _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From dan at kernelim.com Thu Jun 9 21:11:52 2016 From: dan at kernelim.com (Dan Aloni) Date: Fri, 10 Jun 2016 00:11:52 +0300 Subject: cpphs bug with pathnames beginning with more than one slash Message-ID: <20160609211152.GA9246@gmail.com> Hi Malcolm, If we pass pathnames starting with more than one slash to '-include', cpphs generates invalid output. These are valid UNIX pathnames. I've tested with version 1.20.1 on Linux. Example: $ touch empty.hs $ cpphs --cpp -include //dev/null empty.hs #line 1 "test.hs" #line 1 " #line 2 "test.hs" #line 1 "test.hs" If I remove the extra '/', I get a good output: $ touch empty.hs $ cpphs --cpp -include /dev/null empty.hs #line 1 "test.hs" #line 1 "/dev/null" #line 2 "test.hs" #line 1 "test.hs" Thanks. -- Dan Aloni From asr at eafit.edu.co Fri Jun 10 00:44:55 2016 From: asr at eafit.edu.co (=?UTF-8?B?QW5kcsOpcyBTaWNhcmQtUmFtw61yZXo=?=) Date: Thu, 9 Jun 2016 19:44:55 -0500 Subject: cpphs bug with pathnames beginning with more than one slash In-Reply-To: <20160609211152.GA9246@gmail.com> References: <20160609211152.GA9246@gmail.com> Message-ID: Hi Dan, FYI, cpphs has a (new) bug tracker in https://github.com/malcolmwallace/cpphs/issues Best, On 9 June 2016 at 16:11, Dan Aloni wrote: > Hi Malcolm, > > If we pass pathnames starting with more than one slash to '-include', > cpphs generates invalid output. These are valid UNIX pathnames. > I've tested with version 1.20.1 on Linux. > > Example: > > $ touch empty.hs > $ cpphs --cpp -include //dev/null empty.hs > #line 1 "test.hs" > #line 1 " > #line 2 "test.hs" > #line 1 "test.hs" > > If I remove the extra '/', I get a good output: > > $ touch empty.hs > $ cpphs --cpp -include /dev/null empty.hs > #line 1 "test.hs" > #line 1 "/dev/null" > #line 2 "test.hs" > #line 1 "test.hs" > > Thanks. > > -- > Dan Aloni > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > "La informaci?n contenida en este correo electr?nico est? dirigida ?nicamente a su destinatario y puede contener informaci?n confidencial, material privilegiado o informaci?n protegida por derecho de autor. Est? prohibida cualquier copia, utilizaci?n, indebida retenci?n, modificaci?n, difusi?n, distribuci?n o reproducci?n total o parcial. Si usted recibe este mensaje por error, por favor contacte al remitente y elim?nelo. La informaci?n aqu? contenida es responsabilidad exclusiva de su remitente por lo tanto la Universidad EAFIT no se hace responsable de lo que el mensaje contenga." > > "The information contained in this email is addressed to its recipient only and may contain confidential information, privileged material or information protected by copyright. Its prohibited any copy, use, improper retention, modification, dissemination, distribution or total or partial reproduction. If you receive this message by error, please contact the sender and delete it. The information contained herein is the sole responsibility of the sender therefore Universidad EAFIT is not responsible for what the message contains." -- Andr?s "La informaci?n contenida en este correo electr?nico est? dirigida ?nicamente a su destinatario y puede contener informaci?n confidencial, material privilegiado o informaci?n protegida por derecho de autor. Est? prohibida cualquier copia, utilizaci?n, indebida retenci?n, modificaci?n, difusi?n, distribuci?n o reproducci?n total o parcial. Si usted recibe este mensaje por error, por favor contacte al remitente y elim?nelo. La informaci?n aqu? contenida es responsabilidad exclusiva de su remitente por lo tanto la Universidad EAFIT no se hace responsable de lo que el mensaje contenga." "The information contained in this email is addressed to its recipient only and may contain confidential information, privileged material or information protected by copyright. Its prohibited any copy, use, improper retention, modification, dissemination, distribution or total or partial reproduction. If you receive this message by error, please contact the sender and delete it. The information contained herein is the sole responsibility of the sender therefore Universidad EAFIT is not responsible for what the message contains." From dan at kernelim.com Fri Jun 10 02:55:16 2016 From: dan at kernelim.com (Dan Aloni) Date: Fri, 10 Jun 2016 05:55:16 +0300 Subject: cpphs bug with pathnames beginning with more than one slash In-Reply-To: References: <20160609211152.GA9246@gmail.com> Message-ID: <20160610025516.GA14598@gmail.com> On Thu, Jun 09, 2016 at 07:44:55PM -0500, Andr?s Sicard-Ram?rez wrote: > Hi Dan, > > FYI, cpphs has a (new) bug tracker in > > https://github.com/malcolmwallace/cpphs/issues Would be worth linking to it from the docs and main site. I see t there's an open issue there for that :) -- Dan Aloni From hvriedel at gmail.com Fri Jun 10 07:55:19 2016 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Fri, 10 Jun 2016 09:55:19 +0200 Subject: Why upper bound version numbers? In-Reply-To: (David Fox's message of "Thu, 9 Jun 2016 10:43:42 -0700") References: <878tyhplsn.fsf@gmail.com> Message-ID: <87porplbq0.fsf@gmail.com> On 2016-06-09 at 19:43:42 +0200, David Fox wrote: >> or even worse silent failures where the code behaves >> subtly wrong or different than expected. Testsuites mitigate this to >> some degree, but they too are an imperfect solution to this hard >> problem. > ?It seems to me that if you have any thought at all for your library's > clients the chances of this happening are pretty insignificant. This is a common argument, and requires for APIs to avoid changing the semantics of existing operations in the API in a non-backward compatible way. And instead of modifying existing APIs/operations if this can't be done, introduce new operations ( foo, fooV2, fooV3, ...), effectively versioning at the function-level. If we did this consequently, we wouldn't need the PVP to provide us a semantic contract, as upper bounds would only ever be needed/added if somebody broke that eternal compatibility contract. A variation would be to only allow to change the semantics of existing symbols if the type-signature changes in a significant way, and thereby indexing/versioning the semantics by type-signatures rather than a numeric API version. In both cases, we also could dispose of the PVP, as then we could use the API signature as the contract predicting API compatibility (c.f. Backpack) In the former case, we could get away with lower bounds only, and since *the raison d'?tre of the PVP is predicting upper version bounds*, again, there would be no reason to follow the PVP anymore. The PVP is there so I have the means to communicate semantic changes to my libraries' clients in the first place. So while I don't usually deliberately break the API for fun, when I do, I perform using a major version increment to communicate this to my clients. In other words, I promise to do my best not to break my library's API until the next major version bump, and to signal API additions via minor version increments. That's the gist of the PVP contract. In addition to version numbers for the cabal meta-data & solver, I typically also provide a Changelog for humans to read, which (at the very least) describes the reasons for minor & major version increments. If clients of my library choose to deliberately ignore the contract I'm promising to uphold to the best of my abilities (by e.g. leaving off upper bounds), then it's flat-out the client library's author fault that code breaks for disrespecting the PVP. Certainly not mine, as *I* did follow the rules. -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 818 bytes Desc: not available URL: From mgsloan at gmail.com Fri Jun 10 21:16:44 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Fri, 10 Jun 2016 14:16:44 -0700 Subject: Template Haskell determinism In-Reply-To: <1465146843-sup-5444@sabre> References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> <1465146843-sup-5444@sabre> Message-ID: Hey, sorry for not getting back to this sooner! Perhaps I should have added the following to my list of goals in contention: (3) (==) shouldn't yield True for Names that have different unique ids. We can only have stable comparisons if goal (3) isn't met, and two different unique Names would be considered to be equivalent based on the nameBase. This is because Ord is a total order, not a partial order. As described in my prior email, PartialOrd could be added, but it'd be inconvenient to use with existing Ord based containers. -Michael On Sun, Jun 5, 2016 at 10:15 AM, Edward Z. Yang wrote: > I must admit, I am a bit confused by this discussion. > > It is true that every Name is associated with a Unique. But you don't > need the Unique to equality/ordering tests; the names also contain > enough (stable) information for stable comparisons of that sort. So > why don't we expose that instead of the Unique? > > Edward > > Excerpts from Michael Sloan's message of 2016-06-04 18:44:03 -0700: > > On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones < > simonpj at microsoft.com> > > wrote: > > > > > If names get different ordering keys when reified from different > modules > > > (seems like they'd have to, particularly given ghc's "-j"), then we > end up > > > with an unpleasant circumstance where these do not compare as equal > > > > > > > > > > > > The I believe that global, top level names (NameG) are not subject to > this > > > ordering stuff, so I don?t think this problem can occur. > > > > > > > True, top level names are NameG. The reified Info for a top level Dec > may > > include NameU, though. For example, the type variables in 'Maybe' are > > NameU: > > > > $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe > > lift (show nf)) > > > > The resulting expression is something like "NameU 822083586" > > > > > This is a breaking change and it doesn't fix the problem that > NameFlavour > > > is > > > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > > > > > But why is NameU exposed to clients? GHC needs to know, but clients > > > don?t. What use are these packages making of it? > > > > > > > It's being leaked in the public inteface via Ord. The Eq instance is > fine, > > because these are Uniques, so the results should be consistent. > > > > There are two goals in contention here: > > > > 1) Having some ordering on Names so that they can be used in Map or Set > > 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to > > really handle these well. In that case, the ordering would be based on > > everything but the NameU int, but 'Eq' would still follow it > > > > A few ideas for different approaches to resolving this: > > > > 1) Document it. Less appealing than fixing it in the API, but still > would > > be good. > > > > 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' > > newtype (partial ord on the non-unique info), or 'UnstableNameOrd' > newtype > > (current behavior). A trickyness of this approach is that you'd need > > containers that can handle (PartialOrd k, Eq k) keys. In lots of cases > > people are using the 'Ord' instance with 'Name's that are not 'NameU', so > > this would break a lot of code that was already deterministic. > > > > 3) Some approaches like this ordering key, but I'm not sure how it will > > help when comparing NameUs from different modules? > > > > > S > > > > > > > > > > > > > > > > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of > *Michael > > > Sloan > > > *Sent:* 02 June 2016 02:07 > > > *To:* Bartosz Nitka > > > *Cc:* ghc-devs Devs > > > *Subject:* Re: Template Haskell determinism > > > > > > > > > > > > +1 to solving this. Not sure about the approach, but assuming the > > > following concerns are addressed, I'm (+1) on it too: > > > > > > > > > > > > This solution is clever! However, I think there is some difficulty to > > > determining this ordering key. Namely, what happens when I construct > the > > > (Set Name) using results from multiple reifies? > > > > > > > > > > > > One solution is to have the ordering key be a consecutive supply that's > > > initialized on a per-module basis. There is still an issue there, > though, > > > which is that you might store one of these names in a global IORef > that's > > > used by a later TH splice. Or, similarly, serialize the names to a > file > > > and later load them. At least in those cases you need to use 'runIO' > to > > > break determinism. > > > > > > > > > > > > If names get different ordering keys when reified from different > modules > > > (seems like they'd have to, particularly given ghc's "-j"), then we > end up > > > with an unpleasant circumstance where these do not compare as equal. > How > > > about having the Eq instance ignore the ordering key? I think that > mostly > > > resolves this concern. This implies that the Ord instance should also > > > yield EQ and ignore the ordering key, when the unique key matches. > > > > > > > > > > > > One issue with this is that switching the order of reify could > > > unexpectedly vary the behavior. > > > > > > > > > > > > Does the map in TcGblEnv imply that a reify from a later module will > get > > > the same ordering key? So does this mean that the keys used in a given > > > reify depend on which things have already been reified? In that case, > then > > > this is also an issue with your solution. Now, it's not a big problem > at > > > all, just surprising to the user. > > > > > > > > > > > > > > > > > > If the internal API for Name does change, may as well address > > > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's > > > suggested solution of having both the traditional package identifier > and > > > package keys in 'Name'. > > > > > > > > > > > > -Michael > > > > > > > > > > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka > wrote: > > > > > > Template Haskell with its ability to do arbitrary IO is > non-deterministic > > > by > > > > > > design. You could for example embed the current date in a file. There > is > > > > > > however one kind of non-deterministic behavior that you can trigger > > > > > > accidentally. It has to do with how Names are reified. If you take a > look > > > at > > > > > > the definition of reifyName you can see that it puts the assigned > Unique > > > in a > > > > > > NameU: > > > > > > > > > > > > reifyName :: NamedThing n => n -> TH.Name > > > > > > reifyName thing > > > > > > | isExternalName name = mk_varg pkg_str mod_str occ_str > > > > > > | otherwise = TH.mkNameU occ_str (getKey (getUnique > name)) > > > > > > ... > > > > > > NameFlavour which NameU is a constructor of has a default Ord instance, > > > meaning > > > > > > that it ends up comparing the Uniques. The relative ordering of > Uniques is > > > not > > > > > > guaranteed to be stable across recompilations [1], so this can lead to > > > > > > ABI-incompatible binaries. > > > > > > > > > > > > This isn't an abstract problem and it actually happens in practice. The > > > > > > microlens package keeps Names in a Set and later turns that set into a > > > list. > > > > > > The results have different orders of TyVars resulting in different ABI > > > hashes > > > > > > and can potentially be optimized differently. > > > > > > > > > > > > I believe it's worth to handle this case in a deterministic way and I > have > > > a > > > > > > solution in mind. The idea is to extend NameU (and potentially NameL) > with > > > an > > > > > > ordering key. To be more concrete: > > > > > > > > > > > > - | NameU !Int > > > > > > + | NameU !Int !Int > > > > > > > > > > > > This way the Ord instance can use a stable key and the problem reduces > to > > > > > > ensuring the keys are stable. To generate stable keys we can use the > fact > > > that > > > > > > reify traverses the expressions in the same order every time and > > > sequentially > > > > > > allocate new keys based on traversal order. The way I have it > implemented > > > now > > > > > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: > > > > > > > > > > > > + tcg_th_names :: TcRef (UniqFM Int, Int), > > > > > > > > > > > > Then the reifyName and qNewName do the necessary bookkeeping and > translate > > > the > > > > > > Uniques on the fly. > > > > > > > > > > > > This is a breaking change and it doesn't fix the problem that > NameFlavour > > > is > > > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > > > > > - singletons > > > > > > - th-lift > > > > > > - haskell-src-meta > > > > > > - shakespeare > > > > > > - distributed-closure > > > > > > > > > > > > I'd like to get feedback if this is an acceptable solution and if the > > > problem > > > > > > is worth solving. > > > > > > > > > > > > Cheers, > > > > > > Bartosz > > > > > > > > > > > > [1] > > > > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques > > > > > > > > > _______________________________________________ > > > ghc-devs mailing list > > > ghc-devs at haskell.org > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > < > https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c1a4a84c9341546403e1508d38a8246ee%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=mjEDuk%2fuRsDLg0q63zaIBeh5e2IyfKnKjcEcRLDvERE%3d > > > > > > > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From harendra.kumar at gmail.com Sun Jun 12 18:38:38 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Mon, 13 Jun 2016 00:08:38 +0530 Subject: CMM-to-ASM: Register allocation wierdness Message-ID: Hi, I am implementing unicode normalization in Haskell. I challenged myself to match the performance with the best C/C++ implementation, the best being the ICU library. I am almost there, beating it in one of the benchmarks and within 30% for others. I am out of all application level tricks that I could think of and now need help from the compiler. I started with a bare minimum loop and adding functionality incrementally watching where the performance trips. At one point I saw that adding just one 'if' condition reduced the performance by half. I looked at what's going on at the assembly level. Here is a github gist of the assembly instructions executed in the fast path of the loop, corresponding cmm snippets and also the full cmm corresponding to the loop: https://gist.github.com/harendra-kumar/7d34c6745f604a15a872768e57cd2447 I have annotated the assembly code with labels matching the corresponding CMM. With the addition of another "if" condition the loop which was pretty simple till now suddenly got bloated with a lot of register reassignments. Here is a snippet of the register movements added: # _n4se: # swap r14 <-> r11 => 0x408d6b: mov %r11,0x98(%rsp) => 0x408d73: mov %r14,%r11 => 0x408d76: mov 0x98(%rsp),%r14 # reassignments # rbx -> r10 -> r9 -> r8 -> rdi -> rsi -> rdx -> rcx -> rbx => 0x408d7e: mov %rbx,0x90(%rsp) => 0x408d86: mov %rcx,%rbx => 0x408d89: mov %rdx,%rcx => 0x408d8c: mov %rsi,%rdx => 0x408d8f: mov %rdi,%rsi => 0x408d92: mov %r8,%rdi => 0x408d95: mov %r9,%r8 => 0x408d98: mov %r10,%r9 => 0x408d9b: mov 0x90(%rsp),%r10 . . . loop logic here which uses only %rax, %r10 and %r9 . . . . # _n4s8: # shuffle back to original assignments => 0x4090dc: mov %r14,%r11 => 0x4090df: mov %r9,%r10 => 0x4090e2: mov %r8,%r9 => 0x4090e5: mov %rdi,%r8 => 0x4090e8: mov %rsi,%rdi => 0x4090eb: mov %rdx,%rsi => 0x4090ee: mov %rcx,%rdx => 0x4090f1: mov %rbx,%rcx => 0x4090f4: mov %rax,%rbx => 0x4090f7: mov 0x88(%rsp),%rax => 0x4090ff: jmpq 0x408d2a The registers seem to be getting reassigned here, data flowing from one to the next. In this particular path a lot of these register movements seem unnecessary and are only undone at the end without being used. Maybe this is because these are reusable blocks and the movement is necessary when used in some other path? Can this be avoided? Or at least avoided in a certain fast path somehow by hinting the compiler? Any pointers to the GHC code will be appreciated. I am not yet much familiar with the GHC code but can dig deeper pretty quickly. But before that I hope someone knowledgeable in this area can shed some light on this at a conceptual level or if at all it can be improved. I can provide more details and experiment more if needed. Thanks, Harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Sun Jun 12 22:34:38 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 13 Jun 2016 00:34:38 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: Message-ID: <1465770878.3986.5.camel@joachim-breitner.de> Hi, Am Montag, den 13.06.2016, 00:08 +0530 schrieb Harendra Kumar: > Can this be avoided? hopefully, and you already did some great analysis. But sometimes things are moving slow, so if nobody picks it up right away (I think think the number of people who know the register allocator is rather small), make sure you record your findings in a trac ticket, so that they are not lost. Greetings, Joachim -- Joachim ?nomeata? Breitner ? mail at joachim-breitner.de ? https://www.joachim-breitner.de/ ? XMPP: nomeata at joachim-breitner.de?? OpenPGP-Key: 0xF0FBF51F ? Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From harendra.kumar at gmail.com Mon Jun 13 05:46:34 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Mon, 13 Jun 2016 11:16:34 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <1465770878.3986.5.camel@joachim-breitner.de> References: <1465770878.3986.5.camel@joachim-breitner.de> Message-ID: Sure, I will file a ticket once I have more clarity on the problem. BTW, I forgot to mention that this is with ghc-7.10.3. I will try to see how things stand with 8.0.1 at the assembly level though I have not seen any difference in the benchmark performance. I guess it is better to work off 8.0.1 anyway since things might have changed significantly. -harendra On 13 June 2016 at 04:04, Joachim Breitner wrote: > Hi, > > Am Montag, den 13.06.2016, 00:08 +0530 schrieb Harendra Kumar: > > Can this be avoided? > > hopefully, and you already did some great analysis. But sometimes > things are moving slow, so if nobody picks it up right away (I think > think the number of people who know the register allocator is rather > small), make sure you record your findings in a trac ticket, so that > they are not lost. > > Greetings, > Joachim > > -- > > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? https://www.joachim-breitner.de/ > XMPP: nomeata at joachim-breitner.de ? OpenPGP-Key: 0xF0FBF51F > Debian Developer: nomeata at debian.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From harendra.kumar at gmail.com Mon Jun 13 07:29:33 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Mon, 13 Jun 2016 12:59:33 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: Message-ID: My earlier experiment was on GHC-7.10.3. I repeated this on GHC-8.0.1 and the assembly traced was exactly the same except for a marginal improvement. The 8.0.1 code generator removed the r14/r11 swap but the rest of the register ring shift remains the same. I have updated the github gist with the 8.0.1 trace: https://gist.github.com/harendra-kumar/7d34c6745f604a15a872768e57cd2447 thanks, harendra On 13 June 2016 at 00:08, Harendra Kumar wrote: > Hi, > > I am implementing unicode normalization in Haskell. I challenged myself to > match the performance with the best C/C++ implementation, the best being > the ICU library. I am almost there, beating it in one of the benchmarks and > within 30% for others. I am out of all application level tricks that I > could think of and now need help from the compiler. > > I started with a bare minimum loop and adding functionality incrementally > watching where the performance trips. At one point I saw that adding just > one 'if' condition reduced the performance by half. I looked at what's > going on at the assembly level. Here is a github gist of the assembly > instructions executed in the fast path of the loop, corresponding cmm > snippets and also the full cmm corresponding to the loop: > > https://gist.github.com/harendra-kumar/7d34c6745f604a15a872768e57cd2447 > > I have annotated the assembly code with labels matching the corresponding > CMM. > > With the addition of another "if" condition the loop which was pretty > simple till now suddenly got bloated with a lot of register reassignments. > Here is a snippet of the register movements added: > > # _n4se: > # swap r14 <-> r11 > => 0x408d6b: mov %r11,0x98(%rsp) > => 0x408d73: mov %r14,%r11 > => 0x408d76: mov 0x98(%rsp),%r14 > > # reassignments > # rbx -> r10 -> r9 -> r8 -> rdi -> rsi -> rdx -> rcx -> rbx > => 0x408d7e: mov %rbx,0x90(%rsp) > => 0x408d86: mov %rcx,%rbx > => 0x408d89: mov %rdx,%rcx > => 0x408d8c: mov %rsi,%rdx > => 0x408d8f: mov %rdi,%rsi > => 0x408d92: mov %r8,%rdi > => 0x408d95: mov %r9,%r8 > => 0x408d98: mov %r10,%r9 > => 0x408d9b: mov 0x90(%rsp),%r10 > . > . > . > loop logic here which uses only %rax, %r10 and %r9 . > . > . > . > # _n4s8: > # shuffle back to original assignments > => 0x4090dc: mov %r14,%r11 > => 0x4090df: mov %r9,%r10 > => 0x4090e2: mov %r8,%r9 > => 0x4090e5: mov %rdi,%r8 > => 0x4090e8: mov %rsi,%rdi > => 0x4090eb: mov %rdx,%rsi > => 0x4090ee: mov %rcx,%rdx > => 0x4090f1: mov %rbx,%rcx > => 0x4090f4: mov %rax,%rbx > => 0x4090f7: mov 0x88(%rsp),%rax > > => 0x4090ff: jmpq 0x408d2a > > > The registers seem to be getting reassigned here, data flowing from one to > the next. In this particular path a lot of these register movements seem > unnecessary and are only undone at the end without being used. > > Maybe this is because these are reusable blocks and the movement is > necessary when used in some other path? > > Can this be avoided? Or at least avoided in a certain fast path somehow by > hinting the compiler? Any pointers to the GHC code will be appreciated. I > am not yet much familiar with the GHC code but can dig deeper pretty > quickly. But before that I hope someone knowledgeable in this area can shed > some light on this at a conceptual level or if at all it can be improved. I > can provide more details and experiment more if needed. > > Thanks, > Harendra > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Mon Jun 13 11:01:19 2016 From: lonetiger at gmail.com (Phyx) Date: Mon, 13 Jun 2016 13:01:19 +0200 Subject: CoreToStg Asserts Message-ID: Hi *, I'm hoping someone could help me understand what the asserts in CoreToStg on line 240 and 216 are trying to tell me. I hit both of them while trying to compile libraries as dyn. WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 $trModule2 False True ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.1.20160612 for x86_64-unknown-mingw32): ASSERT failed! file compiler\stgSyn\CoreToStg.hs line 216 $trModule2 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug WARNING: file compiler\simplCore\SimplCore.hs, line 633 Simplifier bailing out after 4 iterations [6737, 736, 51, 9] Size = {terms: 12,990, types: 9,998, coercions: 443} WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 $fEqBigNat_$c/= False True ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.1.20160612 for x86_64-unknown-mingw32): ASSERT failed! file compiler\stgSyn\CoreToStg.hs line 240 [$fEqBigNat_$c/=, $fEqBigNat] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Kind Regards, Tamar -------------- next part -------------- An HTML attachment was scrubbed... URL: From harendra.kumar at gmail.com Mon Jun 13 11:23:20 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Mon, 13 Jun 2016 16:53:20 +0530 Subject: Force GC calls out of the straight line execution path Message-ID: Hi, I noticed in the generated code (llvm as well as native) that in some cases the GC calls are in the straight path and the regular code is out of the straight line path. Like this: => 0x408fc0: lea 0x30(%r12),%rax => 0x408fc5: cmp 0x358(%r13),%rax => 0x408fcc: jbe 0x408fe9 # notice jbe instead of ja i.e. branch taken in normal case I tried to count in how many cases its happening in my executable and found that its only a small percentage (4-6%) of cases but those cases include the code which runs 99% of the time in my benchmark. Though it does not make a whole lot of difference but the difference is perceptible and especially when it is in a tight loop. Is it possible to somehow force all the GC calls out of the line during code generation? Has it been thought/discussed before? -harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Mon Jun 13 12:34:40 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Mon, 13 Jun 2016 08:34:40 -0400 Subject: Force GC calls out of the straight line execution path In-Reply-To: References: Message-ID: Hi Harendra, Would it be possible for you to provide a minimal example that compiles to such assembly? It's hard to tell if this is an easy case. Also, just to make sure, you're using -O, right? (I'm not sure if we have a related transformation enabled with -O but just to make sure...) 2016-06-13 7:23 GMT-04:00 Harendra Kumar : > Hi, > > I noticed in the generated code (llvm as well as native) that in some cases > the GC calls are in the straight path and the regular code is out of the > straight line path. Like this: > > => 0x408fc0: lea 0x30(%r12),%rax > => 0x408fc5: cmp 0x358(%r13),%rax > => 0x408fcc: jbe 0x408fe9 # notice jbe instead of ja > i.e. branch taken in normal case > > I tried to count in how many cases its happening in my executable and found > that its only a small percentage (4-6%) of cases but those cases include the > code which runs 99% of the time in my benchmark. Though it does not make a > whole lot of difference but the difference is perceptible and especially > when it is in a tight loop. > > Is it possible to somehow force all the GC calls out of the line during code > generation? Has it been thought/discussed before? > > -harendra > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From harendra.kumar at gmail.com Mon Jun 13 13:34:20 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Mon, 13 Jun 2016 19:04:20 +0530 Subject: Force GC calls out of the straight line execution path In-Reply-To: References: Message-ID: Hi ?mer, I just checked and I do not see this behavior in 8.0.1 native code, it is only seen in 7.10.3. So I guess this got fixed in 8.0. How about the llvm generated code? Can we control this behavior for llvm generated code as well? I first noticed this in llvm generated code with ghc-7.10.3. I do not yet have llvm-3.7 installed to verify the same on 8.0.1. -harendra On 13 June 2016 at 18:04, ?mer Sinan A?acan wrote: > Hi Harendra, > > Would it be possible for you to provide a minimal example that compiles to > such > assembly? It's hard to tell if this is an easy case. > > Also, just to make sure, you're using -O, right? (I'm not sure if we have a > related transformation enabled with -O but just to make sure...) > > 2016-06-13 7:23 GMT-04:00 Harendra Kumar : > > Hi, > > > > I noticed in the generated code (llvm as well as native) that in some > cases > > the GC calls are in the straight path and the regular code is out of the > > straight line path. Like this: > > > > => 0x408fc0: lea 0x30(%r12),%rax > > => 0x408fc5: cmp 0x358(%r13),%rax > > => 0x408fcc: jbe 0x408fe9 # notice jbe instead of > ja > > i.e. branch taken in normal case > > > > I tried to count in how many cases its happening in my executable and > found > > that its only a small percentage (4-6%) of cases but those cases include > the > > code which runs 99% of the time in my benchmark. Though it does not make > a > > whole lot of difference but the difference is perceptible and especially > > when it is in a tight loop. > > > > Is it possible to somehow force all the GC calls out of the line during > code > > generation? Has it been thought/discussed before? > > > > -harendra > > > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 13 13:44:49 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 13 Jun 2016 13:44:49 +0000 Subject: haddock Message-ID: <4b0cad30ab5f4daa84b2586a948dcb17@DB4PR30MB030.064d.mgd.msft.net> Ah! I forgot to push a one-line difff to haddock, which is breaking the build. Sorry. Gotta go right now but will do tonight. Meanwhile all should be ok if you swtich off Haddock Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Mon Jun 13 19:32:26 2016 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Mon, 13 Jun 2016 15:32:26 -0400 Subject: Inferring instance constraints with DeriveAnyClass Message-ID: Andres, I'm trying to think of a proper solution to Trac #12144 [1]. This bug triggers when you try to use DeriveAnyClass in a somewhat exotic fashion: {-# LANGUAGE DeriveAnyClass, KindSignatures #-} class C (a :: * -> *) data T a = MkT (a -> Int) deriving C This currently gives a GHC panic: ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): contravariant This baffled me until I realized why it's happening: for typeclasses of kind * -> *, DeriveAnyClass simply re-uses the same algorithm that DeriveFunctor uses for coming up with an instance context. For instance, if you have: data T f a = MkT a (f a) deriving (Functor, C) Then it would generate two instances of the form: instance Functor f => Functor (T f) where ... instance C f => C (T f) where ... But #12144 reveals the fatal downside of doing this: DeriveFunctor has special knowledge about type parameters in contravariant positions, but this doesn't even make sense to think about with a class like C! (The only reason GHC won't panic if a Functor instance is derived for T is because there are Functor-specific checks that cause an error message to pop up before the panic can be reached.) My question is then: why does DeriveAnyClass take the bizarre approach of co-opting the DeriveFunctor algorithm? Andres, you originally proposed this in #7346 [2], but I don't quite understand why you wanted to do it this way. Couldn't we infer the context simply from the contexts of the default method type signatures? This is a question that Reid Barton has also asked, to which Jos? Pedro Magalh?es answered in the negatory [3]. But Pedro's reasoning has never quite made sense to me, because we've been able to typecheck constraints arising from default method type signatures for a long time, so why would it be impractical to do so in this case? I'd appreciate hearing a more detailed explanation on this issue, because at the moment, I am completely stuck on figuring out how one might fix #12144. Regards, Ryan S. ----- [1] https://ghc.haskell.org/trac/ghc/ticket/12144 [2] https://ghc.haskell.org/trac/ghc/ticket/7346 [3] https://ghc.haskell.org/trac/ghc/ticket/5462#comment:30 From simonpj at microsoft.com Mon Jun 13 21:13:46 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 13 Jun 2016 21:13:46 +0000 Subject: Pusing to haddock Message-ID: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> Devs, I want to push to the haddock repo, to fix the build. But I can?t. .git/modules/utils/haddock/ contains [remote "origin"] url = git://git.haskell.org/haddock.git pushurl = ssh://git at git.haskell.org/haddock.git fetch = +refs/heads/*:refs/remotes/origin/* I?m on branch ghc-head. But when I push I get /cygdrive/c/code/HEAD/utils/haddock$ git push remote: W refs/heads/ghc-head haddock simonpj DENIED by refs/.* remote: error: hook declined to update refs/heads/ghc-head To ssh://git at git.haskell.org/haddock.git ! [remote rejected] ghc-head -> ghc-head (hook declined) error: failed to push some refs to 'ssh://git at git.haskell.org/haddock.git' No info on WHY it rejected. What now? I attach the patch if someone else would like to push. If you do, update ghc HEAD to match Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: spj-haddock-patch Type: application/octet-stream Size: 4150 bytes Desc: spj-haddock-patch URL: From ben at smart-cactus.org Mon Jun 13 21:44:14 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Mon, 13 Jun 2016 23:44:14 +0200 Subject: Pusing to haddock In-Reply-To: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <87twgw69xt.fsf@smart-cactus.org> Simon Peyton Jones writes: > Devs, > I want to push to the haddock repo, to fix the build. But I can?t. > .git/modules/utils/haddock/ contains > > [remote "origin"] > > url = git://git.haskell.org/haddock.git > > pushurl = ssh://git at git.haskell.org/haddock.git > > fetch = +refs/heads/*:refs/remotes/origin/* > I?m on branch ghc-head. But when I push I get > > /cygdrive/c/code/HEAD/utils/haddock$ git push > > remote: W refs/heads/ghc-head haddock simonpj DENIED by refs/.* > > remote: error: hook declined to update refs/heads/ghc-head > > To ssh://git at git.haskell.org/haddock.git > > ! [remote rejected] ghc-head -> ghc-head (hook declined) > > error: failed to push some refs to 'ssh://git at git.haskell.org/haddock.git' > No info on WHY it rejected. > Hmm, I suspect this means that you (or perhaps just this key?) don't have push permission to the haskell.org Haddock repository. We should rectify this. Herbert, could you verify this when you get a chance? > What now? I attach the patch if someone else would like to push. If > you do, update ghc HEAD to match I'll take care of this. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From simonpj at microsoft.com Mon Jun 13 22:09:02 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 13 Jun 2016 22:09:02 +0000 Subject: Pusing to haddock In-Reply-To: <87twgw69xt.fsf@smart-cactus.org> References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> Message-ID: | Hmm, I suspect this means that you (or perhaps just this key?) don't | have push permission to the haskell.org Haddock repository. We should | rectify this. Herbert, could you verify this when you get a chance? I'm sure I used to be able to. I know I've done this before. | > What now? I attach the patch if someone else would like to push. If | > you do, update ghc HEAD to match | | I'll take care of this. Thanks. All builds currently broken because of this.. my fault, sorry! Simon From hvriedel at gmail.com Mon Jun 13 22:13:58 2016 From: hvriedel at gmail.com (Herbert Valerio Riedel) Date: Tue, 14 Jun 2016 00:13:58 +0200 Subject: Pusing to haddock In-Reply-To: <87twgw69xt.fsf@smart-cactus.org> (Ben Gamari's message of "Mon, 13 Jun 2016 23:44:14 +0200") References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> Message-ID: <87shwg3ffd.fsf@gmail.com> On 2016-06-13 at 23:44:14 +0200, Ben Gamari wrote: > Simon Peyton Jones writes: >> Devs, >> I want to push to the haddock repo, to fix the build. But I can?t. >> .git/modules/utils/haddock/ contains >> >> [remote "origin"] >> >> url = git://git.haskell.org/haddock.git >> >> pushurl = ssh://git at git.haskell.org/haddock.git well, that's incorrect... if you look in the 'packages' text-file at the top of GHC's source-tree, you'll notice that haddock's upstream repo is declared as ssh://git at github.com/haskell/haddock.git And you should have permission to push there. git.haskell.org/haddock.git is a mirror of the GitHub repo From simonpj at microsoft.com Mon Jun 13 22:54:47 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 13 Jun 2016 22:54:47 +0000 Subject: Pusing to haddock In-Reply-To: <87shwg3ffd.fsf@gmail.com> References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> <87shwg3ffd.fsf@gmail.com> Message-ID: | if you look in the 'packages' text-file at the top of GHC's source-tree, | you'll notice that haddock's upstream repo is declared as | ssh://git at github.com/haskell/haddock.git | | And you should have permission to push there. Oh yes, thanks -- I'd forgotten that AGAIN. I have now pushed to both the Haddock repo, and the submodule update to master. I hope that should settle things. Ben you can stand down. Simon From mail at joachim-breitner.de Tue Jun 14 07:53:30 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 14 Jun 2016 09:53:30 +0200 Subject: Pusing to haddock In-Reply-To: References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> <87shwg3ffd.fsf@gmail.com> Message-ID: <1465890810.1581.15.camel@joachim-breitner.de> Hi, Am Montag, den 13.06.2016, 22:54 +0000 schrieb Simon Peyton Jones: > I hope that should settle things. it does, but unfortunately, now perf.haskell.org can only give aggregate results for the joint commit: Benchmark name? previous? change? now? nofib/time/fannkuch-redux? 2.838? + 3.74%? 2.944? seconds nofib/time/scs? 0.338? - 3.55%? 0.326? seconds testsuite/expected failures? 114? + 1? 115? tests testsuite/unexpected failures? 1? - 1? 0? tests testsuite/unexpected stats? 0? + 2? 2? tests tests/alloc/haddock.Cabal? 11811321368? + 6.40%? 12567003040? bytes tests/alloc/haddock.compiler? 60211764264? + 7.39%? 64658444232? bytes Both the fannkuch-redux and the scs improvement are probably not interesting; both merely goes back to the state before Simon?s NUMA patch, which indicates a performance cliff (discussed at?https://phabricator.haskell.org/rGHC9e5ea67e268be2659cd30ebaed7044d298198ab0) The haddock stats changes are probably genuine, I assume, but the expected value in all.T should be updated. Greetings, Joachim -- Joachim ?nomeata? Breitner ? mail at joachim-breitner.de ? https://www.joachim-breitner.de/ ? XMPP: nomeata at joachim-breitner.de?? OpenPGP-Key: 0xF0FBF51F ? Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From simonpj at microsoft.com Tue Jun 14 08:18:20 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 14 Jun 2016 08:18:20 +0000 Subject: Pusing to haddock In-Reply-To: <1465890810.1581.15.camel@joachim-breitner.de> References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> <87shwg3ffd.fsf@gmail.com> <1465890810.1581.15.camel@joachim-breitner.de> Message-ID: | tests/alloc/haddock.Cabal? 11811321368? + 6.40%? 12567003040 | bytes | tests/alloc/haddock.compiler? 60211764264? + 7.39% | 64658444232? bytes | | The haddock stats changes are probably genuine, I assume, but the | expected value in all.T should be updated. | I'm sad about this. My changes should have had no visible performance impact. But I'm not set up to dig into why this one patch might have had such large impact on Haddock. Presumably it's not Haddock per-se but perhaps the GHC session that it invokes. I am not sure what to do... I'm quite reluctant to cause a 7% regression in allocation without investigation. I suppose I or someone should investigate before-and-after, but I don't have time to do that this week. If someone felt able to have a go, that'd be fantastic. Otherwise let's at least make a ticket. For the record, the series of patches, one of which presumably causes the regression, is below. Bisecting to the right one would be very helpful -- but you have to apply the final one (haddock-update) first. Sigh. I should be more careful. Simon commit d55a9b4fd5a3ce24b13311962bca66155b17a558 Author: Simon Peyton Jones Date: Mon Jun 13 18:28:30 2016 +0100 Update Haddock to follow change in LHsSigWcType Update submodule to accompany this commit: commit 15b9bf4ba4ab47e6809bf2b3b36ec16e502aea72 Author: Simon Peyton Jones Date: Sat Jun 11 23:49:27 2016 +0100 Improve typechecking of let-bindings Sorry it's late! commit 0497ee504cc9ac5d6babee9b98bf779b3fc50b98 Author: Bartosz Nitka Date: Thu Jun 9 08:50:32 2016 -0700 Make the Ord Module independent of Unique order The `Ord Module` instance currently uses `Unique`s for comparison. We don't want to use the `Unique` order because it can introduce nondeterminism. This switches `Ord ModuleName` and `Ord UnitId` to use lexicographic ordering making `Ord Module` deterministic transitively. I've run `nofib` and it doesn't make a measurable difference. See also Note [ModuleEnv determinism and performance]. Test Plan: ./validate run nofib: P112 Reviewers: simonpj, simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2030 GHC Trac Issues: #4012 commit 586d55815401c54f4687d053fb033e53865e0bf1 Author: Bartosz Nitka Date: Mon Jun 13 07:35:32 2016 -0700 Use UniqFM for SigOf Summary: The Ord instance for ModuleName is currently implemented in terms of Uniques causing potential determinism problems. I plan to change it to use the actual FastStrings and in preparation for that I'm switching to UniqFM where it's possible (you need *one* Unique per key, and you can't get the keys back), so that the performance doesn't suffer. Test Plan: ./validate Reviewers: simonmar, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2320 GHC Trac Issues: #4012 commit 7de776cfe7825fca6a71fe6b3854c3c86bf9ca12 Author: Bartosz Nitka Date: Mon Jun 13 04:53:43 2016 -0700 Kill unused foldModuleEnv With the current implementation, it's nondeterministic because Ord Module is nondeterministic. commit 5cee88d766723929f789ffcd2ef24d8b5ef62a16 Author: Tamar Christina Date: Mon Jun 13 13:29:17 2016 +0200 Add thin library support to Windows too Summary: Code already existed in the RTS to add thin library support for non-Windows operating systems. This adds it to Windows as well. ar thin libraries have the exact same format as normal archives except they have a different magic string and they don't copy the object files into the archive. Instead each header entry points to the location of the object file on disk. This is useful when a library is only created to satisfy a compile time dependency instead of to be distributed. This saves the time required for copying. Test Plan: ./validate and new test T11788 Reviewers: austin, bgamari, simonmar, erikd Reviewed By: bgamari, simonmar Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2323 GHC Trac Issues: #11788 commit 1dcb32ddba605bced2e0e0ce3f52b58e8ff33f5b Author: Simon Peyton Jones Date: Mon Jun 13 12:02:54 2016 +0100 A second test for Trac #12055 This one omits the extension, thereby making GHC 8.0 produce "GHC internal error". commit 921ebc9f0854d033cbafd43d3b2c5ba679c27b3c Author: Simon Peyton Jones Date: Mon Jun 13 11:56:44 2016 +0100 Test Trac #12055 commit e064f501d76c208ddab3c3be551ffe5167d7974f Author: Simon Peyton Jones Date: Sun Jun 12 22:32:31 2016 +0100 Add to .gitignore This adds *.patch *.stackdump (Windows) foo* (simonpj uses foo* for junk files) commit 8104f7c674d7ef2db0c25312f48763202dcef57f Author: Simon Peyton Jones Date: Sun Jun 12 22:01:49 2016 +0100 Remove some traceTc calls During the kind-checking "knot" we have to be careful not to print too eagerly. commit 599d912f0b85583e389661d85ed2f198e2621bb0 Author: Simon Peyton Jones Date: Sun Jun 12 00:06:31 2016 +0100 Beef up isPredTy isPredTy can be called on ill-kinded types, especially (of course) if there is a kind error. We don't wnat it to crash, but it was, in piResultTy. This patch introduces piResultTy_maybe, and uses it in isPredTy. Ugh. I dislike this code. It's mainly used to know when we should print types with '=>', and we should probably have a better way to signal that. commit 15fc52819c440f9e9b91ce92fcfda3c264cbe1c1 Author: Simon Peyton Jones Date: Sun Jun 12 00:04:30 2016 +0100 Fix the in-scope set for extendTvSubstWithClone We'd forgotten the variables free in the kind. Ditto extendCvSubstWithClone commit 1f661281a23b6eab83a1144c43e464c0e2d2195a Author: Simon Peyton Jones Date: Sun Jun 12 00:00:53 2016 +0100 Beef up mkNakedCastTy By spotting Refl coercions we can avoid building an awful lot of CastTys. Simple and effective. commit 35c9de7ca053eda472cb446c53bcd2007bfd8394 Author: Simon Peyton Jones Date: Sat Jun 11 23:56:42 2016 +0100 Move the constraint-kind validity check For type synonyms, we need to check that if the RHS has kind Constraint, then we have -XConstraintKinds. For some reason this was done in checkValidType, but it makes more sense to do it in checkValidTyCon. I can't remember quite why I made this change; maybe it fixes a Trac ticket, but if so I forget which. But it's a modest improvement anyway. commit 7afb7adf45216701e4f645676ecc0668f64b424d Author: Simon Peyton Jones Date: Sat Jun 11 23:55:10 2016 +0100 Get in-scope set right in top_instantiate ...thereby being able to replace substThetaUnchecked with substTheta commit c28dde37f3f274a2a1207dd4e175ea79769f5ead Author: Simon Peyton Jones Date: Sat Jun 11 23:51:44 2016 +0100 Tidy up zonkQuantifiedTyVar I managed to eliminate the strange zonkQuantifiedTyVarOrType, which is no longer used. commit 15b9bf4ba4ab47e6809bf2b3b36ec16e502aea72 Author: Simon Peyton Jones Date: Sat Jun 11 23:49:27 2016 +0100 Improve typechecking of let-bindings This major commit was initially triggered by #11339, but it spiraled into a major review of the way in which type signatures for bindings are handled, especially partial type signatures. On the way I fixed a number of other bugs, namely #12069 #12033 #11700 #11339 #11670 The main change is that I completely reorganised the way in which type signatures in bindings are handled. The new story is in TcSigs Note [Overview of type signatures]. Some specific: * Changes in the data types for signatures in TcRnTypes: TcIdSigInfo and new TcIdSigInst * New module TcSigs deals with typechecking type signatures and pragmas. It contains code mostly moved from TcBinds, which is already too big * HsTypes: I swapped the nesting of HsWildCardBndrs and HsImplicitBndsrs, so that the wildcards are on the oustide not the insidde in a LHsSigWcType. This is just a matter of convenient, nothing deep. There are a host of other changes as knock-on effects, and it all took FAR longer than I anticipated :-). But it is a significant improvement, I think. Lots of error messages changed slightly, some just variants but some modest improvements. New tests * typecheck/should_compile * SigTyVars: a scoped-tyvar test * ExPat, ExPatFail: existential pattern bindings * T12069 * T11700 * T11339 * partial-sigs/should_compile * T12033 * T11339a * T11670 One thing to check: * Small change to output from ghc-api/landmines. Need to check with Alan Zimmerman From mail at joachim-breitner.de Tue Jun 14 08:36:47 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 14 Jun 2016 10:36:47 +0200 Subject: Pusing to haddock In-Reply-To: References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> <87shwg3ffd.fsf@gmail.com> <1465890810.1581.15.camel@joachim-breitner.de> Message-ID: <1465893407.1581.18.camel@joachim-breitner.de> Hi, Am Dienstag, den 14.06.2016, 08:18 +0000 schrieb Simon Peyton Jones: > For the record, the series of patches, one of which presumably causes > the regression, is below.?? Bisecting to the right one would be very > helpful -- but you have to apply the final one (haddock-update) > first. I added a hack to the script that runs perf.haskell.org to cherry-pick this final patch if it is told to build something from that version range, and re-started the build of the affected commits. This should narrow it down. Will report back. Greetings, Joachim -- Joachim ?nomeata? Breitner ? mail at joachim-breitner.de ? https://www.joachim-breitner.de/ ? XMPP: nomeata at joachim-breitner.de?? OpenPGP-Key: 0xF0FBF51F ? Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From ben at well-typed.com Tue Jun 14 08:36:17 2016 From: ben at well-typed.com (Ben Gamari) Date: Tue, 14 Jun 2016 10:36:17 +0200 Subject: Pusing to haddock In-Reply-To: References: <9e5eb8bdeda44d678912b91c9b19b93a@DB4PR30MB030.064d.mgd.msft.net> <87twgw69xt.fsf@smart-cactus.org> <87shwg3ffd.fsf@gmail.com> <1465890810.1581.15.camel@joachim-breitner.de> Message-ID: <87pork5fr2.fsf@smart-cactus.org> Simon Peyton Jones writes: > | tests/alloc/haddock.Cabal? 11811321368? + 6.40%? 12567003040 > | bytes > | tests/alloc/haddock.compiler? 60211764264? + 7.39% > | 64658444232? bytes > | > | The haddock stats changes are probably genuine, I assume, but the > | expected value in all.T should be updated. > | > > I'm sad about this. My changes should have had no visible performance > impact. But I'm not set up to dig into why this one patch might have > had such large impact on Haddock. Presumably it's not Haddock per-se > but perhaps the GHC session that it invokes. > > I am not sure what to do... I'm quite reluctant to cause a 7% > regression in allocation without investigation. I suppose I or someone > should investigate before-and-after, but I don't have time to do that > this week. > > If someone felt able to have a go, that'd be fantastic. Otherwise > let's at least make a ticket. > > For the record, the series of patches, one of which presumably causes > the regression, is below. Bisecting to the right one would be very > helpful -- but you have to apply the final one (haddock-update) first. > I've opened #12191 to track this. I'll try to get to it although I have a friend visiting at the moment so time will be a bit tight until Thursday. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From omeragacan at gmail.com Tue Jun 14 16:46:08 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Tue, 14 Jun 2016 12:46:08 -0400 Subject: CoreToStg Asserts In-Reply-To: References: Message-ID: Hi Tamar, Have a look at Note [Disgusting computation of CafRefs] in TidyPgm.hs. The assertion triggered here is the one that checks `hasCafRefs` mentioned in that note matches with actual CAF-ness. Are you using stock GHC? Which version? Do you have a minimal program that reproduces this? 2016-06-13 7:01 GMT-04:00 Phyx : > Hi *, > > I'm hoping someone could help me understand what the asserts in CoreToStg on > line 240 and 216 are trying to tell me. > > I hit both of them while trying to compile libraries as dyn. > > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $trModule2 False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 216 $trModule2 > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > WARNING: file compiler\simplCore\SimplCore.hs, line 633 > Simplifier bailing out after 4 iterations [6737, 736, 51, 9] > Size = {terms: 12,990, types: 9,998, coercions: 443} > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $fEqBigNat_$c/= False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 240 > [$fEqBigNat_$c/=, $fEqBigNat] > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > Kind Regards, > Tamar > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From lonetiger at gmail.com Tue Jun 14 23:25:44 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Wed, 15 Jun 2016 01:25:44 +0200 Subject: CoreToStg Asserts In-Reply-To: References: Message-ID: <57609278.872b1c0a.c9c5f.530a@mx.google.com> Hi ?mer, Thanks for the pointers, should help me find out more. It?s not a stock GHC as I?m working on getting Dynamic linking back on Windows. This assert is triggered on the dyn version of the libs. So something?s bit rotted here. Cheers, Tamar From: ?mer Sinan A?acan Sent: Tuesday, June 14, 2016 18:46 To: Phyx Cc: ghc-devs at haskell.org Subject: Re: CoreToStg Asserts Hi Tamar, Have a look at Note [Disgusting computation of CafRefs] in TidyPgm.hs. The assertion triggered here is the one that checks `hasCafRefs` mentioned in that note matches with actual CAF-ness. Are you using stock GHC? Which version? Do you have a minimal program that reproduces this? 2016-06-13 7:01 GMT-04:00 Phyx : > Hi *, > > I'm hoping someone could help me understand what the asserts in CoreToStg on > line 240 and 216 are trying to tell me. > > I hit both of them while trying to compile libraries as dyn. > > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $trModule2 False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 216 $trModule2 > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > WARNING: file compiler\simplCore\SimplCore.hs, line 633 > Simplifier bailing out after 4 iterations [6737, 736, 51, 9] > Size = {terms: 12,990, types: 9,998, coercions: 443} > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $fEqBigNat_$c/= False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 240 > [$fEqBigNat_$c/=, $fEqBigNat] > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > Kind Regards, > Tamar > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas.dudebout at gmail.com Wed Jun 15 10:34:56 2016 From: nicolas.dudebout at gmail.com (Nicolas Dudebout) Date: Wed, 15 Jun 2016 06:34:56 -0400 Subject: ghc-pkg, package database path containing a trailing slash, and ${pkgroot} Message-ID: When passing a package database to ghc-pkg via GHC_PACKAGE_PATH or --package-db, ${pkgroot} does not get computed properly if the input path contains a trailing slash. Default behavior: $ ghc-pkg describe base | grep pkgroot pkgroot: "/usr/lib/ghc-7.10.2" Correct behavior (no trailing slash): $ ghc-pkg --package-db /usr/lib/ghc-7.10.2/package.conf.d describe base | grep pkgroot pkgroot: "/usr/lib/ghc-7.10.2" $ GHC_PACKAGE_PATH=/usr/lib/ghc-7.10.2/package.conf.d ghc-pkg describe base | grep pkgroot pkgroot: "/usr/lib/ghc-7.10.2" Incorrect behavior (with trailing slash): $ ghc-pkg --package-db /usr/lib/ghc-7.10.2/package.conf.d/ describe base | grep pkgroot pkgroot: "/usr/lib/ghc-7.10.2/package.conf.d" $ GHC_PACKAGE_PATH=/usr/lib/ghc-7.10.2/package.conf.d/ ghc-pkg describe base | grep pkgroot pkgroot: "/usr/lib/ghc-7.10.2/package.conf.d" When this bug happens, ghc-pkg check complains about missing files for packages using ${pkgroot}. This bug happens because ${pkgroot} is computed using takeDirectory. It should instead use (takeDirectory . dropTrailingPathSeparator) -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 15 11:07:35 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 15 Jun 2016 11:07:35 +0000 Subject: CoreToStg Asserts In-Reply-To: <57609278.872b1c0a.c9c5f.530a@mx.google.com> References: <57609278.872b1c0a.c9c5f.530a@mx.google.com> Message-ID: Ah yes. This is a long-standing wart: 1. The CoreTidy pass predicts what will be CAFFY (see https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/CAFs). It predicts that info because the output of CoreTidy is what goes into interface files. 2. The CorePrep pass messes the code a bit 3. The CoreToStg pass coverts to STG, and at that point we know for sure what will be CAFFY and what will not The assert trips when the predication in (1) doesn?t agree with reality in (3). It would be Much Much better if we took the info from (3) and used that to drive the Core-to-IfaceSyn conversion that creates the interface file content. The only reason not to do this is that it?d mean delaying Core-to-IfaceSyn until pass (3) had happened.. possibly bad for space. But maybe it?s a non-issue in practice. See https://ghc.haskell.org/trac/ghc/ticket/9718 Windows interacts with this because with DLLs some pointers that would be static closures turn into thunks (I think). See StgSyn.isDllConApp, and TidyPgm.hasCafRefs Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of lonetiger at gmail.com Sent: 15 June 2016 00:26 To: ?mer Sinan A?acan Cc: ghc-devs at haskell.org Subject: RE: CoreToStg Asserts Hi ?mer, Thanks for the pointers, should help me find out more. It?s not a stock GHC as I?m working on getting Dynamic linking back on Windows. This assert is triggered on the dyn version of the libs. So something?s bit rotted here. Cheers, Tamar From: ?mer Sinan A?acan Sent: Tuesday, June 14, 2016 18:46 To: Phyx Cc: ghc-devs at haskell.org Subject: Re: CoreToStg Asserts Hi Tamar, Have a look at Note [Disgusting computation of CafRefs] in TidyPgm.hs. The assertion triggered here is the one that checks `hasCafRefs` mentioned in that note matches with actual CAF-ness. Are you using stock GHC? Which version? Do you have a minimal program that reproduces this? 2016-06-13 7:01 GMT-04:00 Phyx >: > Hi *, > > I'm hoping someone could help me understand what the asserts in CoreToStg on > line 240 and 216 are trying to tell me. > > I hit both of them while trying to compile libraries as dyn. > > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $trModule2 False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 216 $trModule2 > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > WARNING: file compiler\simplCore\SimplCore.hs, line 633 > Simplifier bailing out after 4 iterations [6737, 736, 51, 9] > Size = {terms: 12,990, types: 9,998, coercions: 443} > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 > $fEqBigNat_$c/= False True > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.1.20160612 for x86_64-unknown-mingw32): > ASSERT failed! > file compiler\stgSyn\CoreToStg.hs line 240 > [$fEqBigNat_$c/=, $fEqBigNat] > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > Kind Regards, > Tamar > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Wed Jun 15 14:47:12 2016 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 15 Jun 2016 10:47:12 -0400 Subject: ghc-pkg, package database path containing a trailing slash, and ${pkgroot} Message-ID: Good catch! This seems like a straightforward bug. Do you mind creating a ticket for this issue on GHC Trac at https://ghc.haskell.org/trac/ghc/newticket ? Best, Ryan S. From lonetiger at gmail.com Wed Jun 15 23:46:21 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Thu, 16 Jun 2016 01:46:21 +0200 Subject: CoreToStg Asserts In-Reply-To: References: <57609278.872b1c0a.c9c5f.530a@mx.google.com> Message-ID: <5761e8cf.aa29c20a.20e25.ffffb981@mx.google.com> Ah, thanks Simon! This helps a lot. Cheers, Tamar From: Simon Peyton Jones Sent: Wednesday, June 15, 2016 13:07 To: lonetiger at gmail.com; ?mer Sinan A?acan Cc: ghc-devs at haskell.org Subject: RE: CoreToStg Asserts Ah yes.? This is a long-standing wart: 1. The CoreTidy pass predicts what will be CAFFY (see https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/CAFs). It predicts that info because the output of CoreTidy is what goes into interface files. 2. The CorePrep pass messes the code a bit 3. The CoreToStg pass coverts to STG, and at that point we know for sure what will be CAFFY and what will not The assert trips when the predication in (1) doesn?t agree with reality in (3). It would be Much Much better if we took the info from (3) and used that to drive the Core-to-IfaceSyn conversion that creates the interface file content. The only reason not to do this is that it?d mean delaying Core-to-IfaceSyn until pass (3) had happened.. possibly bad for space.? But maybe it?s a non-issue in practice. See https://ghc.haskell.org/trac/ghc/ticket/9718 Windows interacts with this because with DLLs some pointers that would be static closures turn into thunks (I think).? See StgSyn.isDllConApp, and TidyPgm.hasCafRefs Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of lonetiger at gmail.com Sent: 15 June 2016 00:26 To: ?mer Sinan A?acan Cc: ghc-devs at haskell.org Subject: RE: CoreToStg Asserts Hi ?mer, Thanks for the pointers, should help me find out more. It?s not a stock GHC as I?m working on getting Dynamic linking back on Windows. This assert is triggered on the dyn version of the libs. So something?s bit rotted here. Cheers, Tamar From: ?mer Sinan A?acan Sent: Tuesday, June 14, 2016 18:46 To: Phyx Cc: ghc-devs at haskell.org Subject: Re: CoreToStg Asserts Hi Tamar, Have a look at Note [Disgusting computation of CafRefs] in TidyPgm.hs. The assertion triggered here is the one that checks `hasCafRefs` mentioned in that note matches with actual CAF-ness. Are you using stock GHC? Which version? Do you have a minimal program that reproduces this? 2016-06-13 7:01 GMT-04:00 Phyx : > Hi *, > > I'm hoping someone could help me understand what the asserts in CoreToStg on > line 240 and 216 are trying to tell me. > > I hit both of them while trying to compile libraries as dyn. > > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 >?? $trModule2 False True > ghc-stage1.exe: panic! (the 'impossible' happened) >?? (GHC version 8.1.20160612 for x86_64-unknown-mingw32): >???????? ASSERT failed! >?? file compiler\stgSyn\CoreToStg.hs line 216 $trModule2 > > Please report this as a GHC bug:? http://www.haskell.org/ghc/reportabug > > WARNING: file compiler\simplCore\SimplCore.hs, line 633 >?? Simplifier bailing out after 4 iterations [6737, 736, 51, 9] >???? Size = {terms: 12,990, types: 9,998, coercions: 443} > WARNING: file compiler\stgSyn\CoreToStg.hs, line 250 >?? $fEqBigNat_$c/= False True > ghc-stage1.exe: panic! (the 'impossible' happened) >?? (GHC version 8.1.20160612 for x86_64-unknown-mingw32): >???????? ASSERT failed! >?? file compiler\stgSyn\CoreToStg.hs line 240 >?? [$fEqBigNat_$c/=, $fEqBigNat] > > Please report this as a GHC bug:? http://www.haskell.org/ghc/reportabug > > Kind Regards, > Tamar > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Thu Jun 16 08:29:39 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 16 Jun 2016 10:29:39 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: Message-ID: <87mvml5yfg.fsf@smart-cactus.org> Harendra Kumar writes: > My earlier experiment was on GHC-7.10.3. I repeated this on GHC-8.0.1 and > the assembly traced was exactly the same except for a marginal improvement. > The 8.0.1 code generator removed the r14/r11 swap but the rest of the > register ring shift remains the same. I have updated the github gist with > the 8.0.1 trace: > Have you tried compiling with -fregs-graph [1] (the graph-coloring allocator)? By default GHC uses a very naive linear register allocator which I'd imagine may produce these sorts of results. At some point there was an effort to make -fregs-graph the default (see #2790) but it is unfortunately quite slow despite having a relatively small impact on produced-code quality in most cases. However, in your case it may be worth enabling. Note, however, that the graph coloring allocator has a few quirks of its own (see #8657 and #7697). It actually came to my attention while researching this that the -fregs-graph flag is currently silently ignored [2]. Unfortunately this means you'll need to build a new compiler if you want to try using it. Simon Marlow: If we really want to disable this option we should at very least issue an error when the user requests it. However, really it seems to me like we shouldn't disable it at all; why not just allow the user to use it and add a note to the documentation stating that the graph coloring allocator may fail with some programs and if it breaks the user gets to keep both pieces? 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. Cheers, - Ben [1] http://downloads.haskell.org/~ghc/master/users-guide//using-optimisation.html?highlight=register%20graph#ghc-flag--fregs-graph [2] https://git.haskell.org/ghc.git/commitdiff/f0a7261a39bd1a8c5217fecba56c593c353f198c -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From ben at smart-cactus.org Thu Jun 16 09:55:41 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 16 Jun 2016 11:55:41 +0200 Subject: ghc-pkg, package database path containing a trailing slash, and ${pkgroot} In-Reply-To: References: Message-ID: <87bn315ug2.fsf@smart-cactus.org> Nicolas Dudebout writes: > When passing a package database to ghc-pkg via GHC_PACKAGE_PATH or > --package-db, ${pkgroot} does not get computed properly if the input path > contains a trailing slash. > Thanks for the report, Nicolas. I've opened #12196 to track this and proposed a fix in D2336. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From harendra.kumar at gmail.com Thu Jun 16 10:53:12 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Thu, 16 Jun 2016 16:23:12 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <87mvml5yfg.fsf@smart-cactus.org> References: <87mvml5yfg.fsf@smart-cactus.org> Message-ID: On 16 June 2016 at 13:59, Ben Gamari wrote: > > It actually came to my attention while researching this that the > -fregs-graph flag is currently silently ignored [2]. Unfortunately this > means you'll need to build a new compiler if you want to try using it. Yes I did try -fregs-graph and -fregs-iterative both. To debug why nothing changed I had to compare the executables produced with and without the flags and found them identical. A note in the manual could have saved me some time since that's the first place to go for help. I was wondering if I am making a mistake in the build and if it is not being rebuilt properly. Your note confirms my observation, it indeed does not change anything. > 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. Yes, I can try that. In fact I was going in that direction and then stopped to look at what llvm does. llvm gave me impressive results in some cases though not so great in others. I compared the code generated by llvm and it perhaps did a better job in theory (used fewer instructions) but due to more spilling the end result was pretty similar. But I found a few interesting optimizations that llvm did. For example, there was a heap adjustment and check in the looping path which was redundant and was readjusted in the loop itself without use. LLVM either removed the redundant _adjustments_ in the loop or moved them out of the loop. But it did not remove the corresponding heap _checks_. That makes me wonder if the redundant heap checks can also be moved or removed. If we can do some sort of loop analysis at the CMM level itself and avoid or remove the redundant heap adjustments as well as checks or at least float them out of the cycle wherever possible. That sort of optimization can make a significant difference to my case at least. Since we are explicitly aware of the heap at the CMM level there may be an opportunity to do better than llvm if we optimize the generated CMM or the generation of CMM itself. A thought that came to my mind was whether we should focus on getting better code out of the llvm backend or the native code generator. LLVM seems pretty good at the specialized task of code generation and low level optimization, it is well funded, widely used and has a big community support. That allows us to leverage that huge effort and take advantage of the new developments. Does it make sense to outsource the code generation and low level optimization tasks to llvm and ghc focussing on higher level optimizations which are harder to do at the llvm level? What are the downsides of using llvm exclusively in future? -harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From karel.gardas at centrum.cz Thu Jun 16 11:18:50 2016 From: karel.gardas at centrum.cz (Karel Gardas) Date: Thu, 16 Jun 2016 13:18:50 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: <87mvml5yfg.fsf@smart-cactus.org> Message-ID: <57628B1A.6050002@centrum.cz> On 06/16/16 12:53 PM, Harendra Kumar wrote: > A thought that came to my mind was whether we should focus on getting > better code out of the llvm backend or the native code generator. LLVM > seems pretty good at the specialized task of code generation and low > level optimization, it is well funded, widely used and has a big > community support. That allows us to leverage that huge effort and take > advantage of the new developments. Does it make sense to outsource the > code generation and low level optimization tasks to llvm and ghc > focussing on higher level optimizations which are harder to do at the > llvm level? What are the downsides of using llvm exclusively in future? Good reading IMHO about the topic is here: https://ghc.haskell.org/trac/ghc/wiki/ImprovedLLVMBackend Cheers, Karel From harendra.kumar at gmail.com Thu Jun 16 12:10:19 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Thu, 16 Jun 2016 17:40:19 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <57628B1A.6050002@centrum.cz> References: <87mvml5yfg.fsf@smart-cactus.org> <57628B1A.6050002@centrum.cz> Message-ID: That's a nice read, thanks for the pointer. I agree with the solution presented there. If we can do that it will be awesome. If help is needed I can spend some time on it. One of the things that I noticed is that the code can be optimized significantly if we know the common case so that we can optimize that path at the expense of less common path. At times I saw wild difference in performance just by a very small change in the source. I could attribute the difference to code blocks having moved and differently placed jump instructions or change in register allocations impacting the common case more. This could be avoided if we know the common case. The common case is not visible or obvious to low level tools. It is easier to write the code in a low level language like C such that it is closer to how it will run on the processor, we can also easily influence gcc from the source level. It is harder to do the same in a high level language like Haskell. Perhaps there is no point in doing so. What we can do instead is to use the llvm toolchain to perform feedback directed optimization and it will adjust the low level code accordingly based on your feedback runs. That will be entirely free since it can be done at the llvm level. My point is that it will pay off in things like that if we invest in integrating llvm better. -harendra On 16 June 2016 at 16:48, Karel Gardas wrote: > On 06/16/16 12:53 PM, Harendra Kumar wrote: > >> A thought that came to my mind was whether we should focus on getting >> better code out of the llvm backend or the native code generator. LLVM >> seems pretty good at the specialized task of code generation and low >> level optimization, it is well funded, widely used and has a big >> community support. That allows us to leverage that huge effort and take >> advantage of the new developments. Does it make sense to outsource the >> code generation and low level optimization tasks to llvm and ghc >> focussing on higher level optimizations which are harder to do at the >> llvm level? What are the downsides of using llvm exclusively in future? >> > > Good reading IMHO about the topic is here: > https://ghc.haskell.org/trac/ghc/wiki/ImprovedLLVMBackend > > Cheers, > Karel > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 16 12:10:18 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 16 Jun 2016 12:10:18 +0000 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <87mvml5yfg.fsf@smart-cactus.org> References: <87mvml5yfg.fsf@smart-cactus.org> Message-ID: | 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 needed. Simon From ben at smart-cactus.org Thu Jun 16 12:37:17 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 16 Jun 2016 14:37:17 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: <87mvml5yfg.fsf@smart-cactus.org> Message-ID: <87y46548ea.fsf@smart-cactus.org> Ccing David Spitzenberg, who has thought about proc-point splitting, which is relevant for reasons that we will see below. Harendra Kumar writes: > On 16 June 2016 at 13:59, Ben Gamari wrote: >> >> It actually came to my attention while researching this that the >> -fregs-graph flag is currently silently ignored [2]. Unfortunately this >> means you'll need to build a new compiler if you want to try using it. > > Yes I did try -fregs-graph and -fregs-iterative both. To debug why nothing > changed I had to compare the executables produced with and without the > flags and found them identical. A note in the manual could have saved me > some time since that's the first place to go for help. I was wondering if I > am making a mistake in the build and if it is not being rebuilt > properly. Your note confirms my observation, it indeed does not change > anything. > Indeed; I've opened D2335 [1] to reenable -fregs-graph and add an appropriate note to the users guide. >> 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. > > Yes, I can try that. In fact I was going in that direction and then stopped > to look at what llvm does. llvm gave me impressive results in some cases > though not so great in others. I compared the code generated by llvm and it > perhaps did a better job in theory (used fewer instructions) but due to > more spilling the end result was pretty similar. > For the record, I have also struggled with register spilling issues in the past. See, for instance, #10012, which describes a behavior which arises from the C-- sinking pass's unwillingness to duplicate code across branches. While in general it's good to avoid the code bloat that this duplication implies, in the case shown in that ticket duplicating the computation would be significantly less code than the bloat from spilling the needed results. > But I found a few interesting optimizations that llvm did. For example, > there was a heap adjustment and check in the looping path which was > redundant and was readjusted in the loop itself without use. LLVM either > removed the redundant _adjustments_ in the loop or moved them out of the > loop. But it did not remove the corresponding heap _checks_. That makes me > wonder if the redundant heap checks can also be moved or removed. If we can > do some sort of loop analysis at the CMM level itself and avoid or remove > the redundant heap adjustments as well as checks or at least float them out > of the cycle wherever possible. That sort of optimization can make a > significant difference to my case at least. Since we are explicitly aware > of the heap at the CMM level there may be an opportunity to do better than > llvm if we optimize the generated CMM or the generation of CMM itself. > Very interesting, thanks for writing this down! Indeed if these checks really are redundant then we should try to avoid them. Do you have any code you could share that demosntrates this? It would be great to open Trac tickets to track some of the optimization opportunities that you noted we may be missing. Trac tickets are far easier to track over longer durations than mailing list conversations, which tend to get lost in the noise after a few weeks pass. > A thought that came to my mind was whether we should focus on getting > better code out of the llvm backend or the native code generator. LLVM > seems pretty good at the specialized task of code generation and low level > optimization, it is well funded, widely used and has a big community > support. That allows us to leverage that huge effort and take advantage of > the new developments. Does it make sense to outsource the code generation > and low level optimization tasks to llvm and ghc focussing on higher level > optimizations which are harder to do at the llvm level? What are the > downsides of using llvm exclusively in future? > There is indeed a question of where we wish to focus our optimization efforts. However, I think using LLVM exclusively would be a mistake. LLVM is a rather large dependency that has in the past been rather difficult to track (this is why we now only target one LLVM release in a given GHC release). Moreover, it's significantly slower than our existing native code generator. There are a number of reasons for this, some of which are fixable. For instance, we currently make no effort to tell LLVM which passes are worth running and which we've handled; this is something which should be fixed but will require a rather significant investment by someone to determine how GHC's and LLVM's passes overlap, how they interact, and generally which are helpful (see GHC #11295). Furthermore, there are a few annoying impedance mismatches between Cmm and LLVM's representation. This can be seen in our treatment of proc points: when we need to take the address of a block within a function LLVM requires that we break the block into a separate procedure, hiding many potential optimizations from the optimizer. This was discussed further on this list earlier this year [2]. It would be great to eliminate proc-point splitting but doing so will almost certainly require cooperation from LLVM. Cheers, - Ben [1] https://phabricator.haskell.org/D2335 [2] https://mail.haskell.org/pipermail/ghc-devs/2015-November/010535.html -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From harendra.kumar at gmail.com Fri Jun 17 09:09:03 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Fri, 17 Jun 2016 14:39:03 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <87y46548ea.fsf@smart-cactus.org> References: <87mvml5yfg.fsf@smart-cactus.org> <87y46548ea.fsf@smart-cactus.org> Message-ID: Thanks Ben! I have my responses inline below. On 16 June 2016 at 18:07, Ben Gamari wrote: > > Indeed; I've opened D2335 [1] to reenable -fregs-graph and add an > appropriate note to the users guide. > Thanks! That was quick. > For the record, I have also struggled with register spilling issues in > the past. See, for instance, #10012, which describes a behavior which > arises from the C-- sinking pass's unwillingness to duplicate code > across branches. While in general it's good to avoid the code bloat that > this duplication implies, in the case shown in that ticket duplicating > the computation would be significantly less code than the bloat from > spilling the needed results. > Not sure if this is possible but when unsure we can try both and compare if the duplication results in significantly more code than no duplication and make a decision based on that. Though that will slow down the compilation. Maybe we can bundle slower passes in something like -O3, meaning it will be slow and may or may not provide better results? > > But I found a few interesting optimizations that llvm did. For example, > > there was a heap adjustment and check in the looping path which was > > redundant and was readjusted in the loop itself without use. LLVM either > > removed the redundant _adjustments_ in the loop or moved them out of the > > loop. But it did not remove the corresponding heap _checks_. That makes > me > > wonder if the redundant heap checks can also be moved or removed. If we > can > > do some sort of loop analysis at the CMM level itself and avoid or remove > > the redundant heap adjustments as well as checks or at least float them > out > > of the cycle wherever possible. That sort of optimization can make a > > significant difference to my case at least. Since we are explicitly aware > > of the heap at the CMM level there may be an opportunity to do better > than > > llvm if we optimize the generated CMM or the generation of CMM itself. > > > Very interesting, thanks for writing this down! Indeed if these checks > really are redundant then we should try to avoid them. Do you have any > code you could share that demosntrates this? > The gist that I provided in this email thread earlier demonstrates it. Here it is again: https://gist.github.com/harendra-kumar/7d34c6745f604a15a872768e57cd2447 If you look at the CMM trace in the gist. Start at label c4ic where we allocate space on heap (+48). Now, there are many possible paths from this point on some of those use the heap and some don't. I have marked those which use the heap by curly braces, the rest do not use it at all. 1) c4ic (allocate) -> c4mw -> {c4pv} -> ... 2) c4ic (allocate) -> c4mw -> c4pw -> ((c4pr -> ({c4pe} -> ... | c4ph -> ...)) | cp4ps -> ...) If we can place this allocation at both c4pv and c4pe instead of the common parent then we can save the fast path from this check. The same thing applies to the allocation at label c4jd as well. I have the code to produce this CMM, I can commit it on a branch and leave it in the github repository so that we can use it for fixing. > It would be great to open Trac tickets to track some of the optimization > Will do. > There is indeed a question of where we wish to focus our optimization > efforts. However, I think using LLVM exclusively would be a mistake. > LLVM is a rather large dependency that has in the past been rather > difficult to track (this is why we now only target one LLVM release in a > given GHC release). Moreover, it's significantly slower than our > existing native code generator. There are a number of reasons for this, > some of which are fixable. For instance, we currently make no effort to > tell > LLVM which passes are worth running and which we've handled; this is > something which should be fixed but will require a rather significant > investment by someone to determine how GHC's and LLVM's passes overlap, > how they interact, and generally which are helpful (see GHC #11295). > > Furthermore, there are a few annoying impedance mismatches between Cmm > and LLVM's representation. This can be seen in our treatment of proc > points: when we need to take the address of a block within a function > LLVM requires that we break the block into a separate procedure, hiding > many potential optimizations from the optimizer. This was discussed > further on this list earlier this year [2]. It would be great to > eliminate proc-point splitting but doing so will almost certainly > require cooperation from LLVM. > It sounds like we need to continue with both for now and see how the llvm option pans out. There is clearly no reason for a decisive tilt towards llvm in near future. -harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Jun 17 11:43:24 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 17 Jun 2016 11:43:24 +0000 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: References: Message-ID: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> | My question is then: why does DeriveAnyClass take the bizarre approach | of co-opting the DeriveFunctor algorithm? Andres, you originally | proposed this in #7346 [2], but I don't quite understand why you | wanted to do it this way. Couldn't we infer the context simply from | the contexts of the default method type signatures? That last suggestion makes perfect sense to me. After all, we are going to generate an instance looking like instance .. => C (T a) where op1 = op2 = so all we need in ".." is enough context to satisfy the needs of etc. Well, you need to take account of the class op type sig too: class C a where op :: Eq a => a -> a default op :: (Eq a, Show a) => a -> a We effectively define default_op :: (Eq a, Show a) => a -> a Now with DeriveAnyClass for lists, we effectively get instance ... => C [a] where op = default_op What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq [a] (because that's op's instantiated type. So Show a is all we need in the end. Simon From ben at smart-cactus.org Fri Jun 17 12:00:17 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 17 Jun 2016 14:00:17 +0200 Subject: Force GC calls out of the straight line execution path In-Reply-To: References: Message-ID: <87inx8rpny.fsf@smart-cactus.org> Harendra Kumar writes: > Hi Ömer, > > I just checked and I do not see this behavior in 8.0.1 native code, it is > only seen in 7.10.3. So I guess this got fixed in 8.0. > > How about the llvm generated code? Can we control this behavior for llvm > generated code as well? I first noticed this in llvm generated code with > ghc-7.10.3. I do not yet have llvm-3.7 installed to verify the same on > 8.0.1. > Indeed that may be the difference. It looks like the LLVM code generator currently ignores the expected value provided by the C-- representation. This is pretty straightforward to fix; see D2339 [1]. Cheers, - Ben [1] https://phabricator.haskell.org/D2339 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From harendra.kumar at gmail.com Fri Jun 17 12:53:57 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Fri, 17 Jun 2016 18:23:57 +0530 Subject: Force GC calls out of the straight line execution path In-Reply-To: <87inx8rpny.fsf@smart-cactus.org> References: <87inx8rpny.fsf@smart-cactus.org> Message-ID: On 17 June 2016 at 17:30, Ben Gamari wrote: > > > [1] https://phabricator.haskell.org/D2339 Awesome! -harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From dreixel at gmail.com Sat Jun 18 08:15:36 2016 From: dreixel at gmail.com (=?UTF-8?Q?Jos=C3=A9_Pedro_Magalh=C3=A3es?=) Date: Sat, 18 Jun 2016 09:15:36 +0100 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> References: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> Message-ID: I still don't think you can do it just from the default method's type. A typical case is the following: class C a where op :: a -> Int default op :: (Generic a, GC (Rep a)) => a -> Int When giving an instance C [a], you might well find out that you need C a =>, but this is not something you can see in the type of the default method; it follows only after the expansion of Rep [a] and resolving the GC constraint a number of times. Best regards, Pedro On Fri, Jun 17, 2016 at 12:43 PM, Simon Peyton Jones wrote: > | My question is then: why does DeriveAnyClass take the bizarre approach > | of co-opting the DeriveFunctor algorithm? Andres, you originally > | proposed this in #7346 [2], but I don't quite understand why you > | wanted to do it this way. Couldn't we infer the context simply from > | the contexts of the default method type signatures? > > That last suggestion makes perfect sense to me. After all, we are going > to generate an instance looking like > > instance .. => C (T a) where > op1 = > op2 = > > so all we need in ".." is enough context to satisfy the needs of > etc. > > Well, you need to take account of the class op type sig too: > > class C a where > op :: Eq a => a -> a > default op :: (Eq a, Show a) => a -> a > > We effectively define > default_op :: (Eq a, Show a) => a -> a > > Now with DeriveAnyClass for lists, we effectively get > > instance ... => C [a] where > op = default_op > > What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq [a] > (because that's op's instantiated type. So Show a is all we need in the > end. > > Simon > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Sat Jun 18 11:51:25 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Sat, 18 Jun 2016 11:51:25 +0000 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: References: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <50a0e2e329474ad89e33a7faee38b990@DB4PR30MB030.064d.mgd.msft.net> Yes, but none of that has anything to do with a walk over the data type, as deriving(Functor) does! You are right that what we need is the result of simplifying the instantiated constraint (Generic [a], GC (Rep [a])) Simplify that constraint (simplifyDeriv does that), including reducing type-function applications, and that’s your context. But no need to look at the data type’s constructors, as deriving(Functor) does. Simon From: josepedromagalhaes at gmail.com [mailto:josepedromagalhaes at gmail.com] On Behalf Of José Pedro Magalhães Sent: 18 June 2016 09:16 To: Simon Peyton Jones Cc: Ryan Scott ; Andres Löh ; GHC developers Subject: Re: Inferring instance constraints with DeriveAnyClass I still don't think you can do it just from the default method's type. A typical case is the following: class C a where op :: a -> Int default op :: (Generic a, GC (Rep a)) => a -> Int When giving an instance C [a], you might well find out that you need C a =>, but this is not something you can see in the type of the default method; it follows only after the expansion of Rep [a] and resolving the GC constraint a number of times. Best regards, Pedro On Fri, Jun 17, 2016 at 12:43 PM, Simon Peyton Jones > wrote: | My question is then: why does DeriveAnyClass take the bizarre approach | of co-opting the DeriveFunctor algorithm? Andres, you originally | proposed this in #7346 [2], but I don't quite understand why you | wanted to do it this way. Couldn't we infer the context simply from | the contexts of the default method type signatures? That last suggestion makes perfect sense to me. After all, we are going to generate an instance looking like instance .. => C (T a) where op1 = op2 = so all we need in ".." is enough context to satisfy the needs of etc. Well, you need to take account of the class op type sig too: class C a where op :: Eq a => a -> a default op :: (Eq a, Show a) => a -> a We effectively define default_op :: (Eq a, Show a) => a -> a Now with DeriveAnyClass for lists, we effectively get instance ... => C [a] where op = default_op What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq [a] (because that's op's instantiated type. So Show a is all we need in the end. Simon _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From dreixel at gmail.com Sat Jun 18 11:55:10 2016 From: dreixel at gmail.com (=?UTF-8?Q?Jos=C3=A9_Pedro_Magalh=C3=A3es?=) Date: Sat, 18 Jun 2016 12:55:10 +0100 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: <50a0e2e329474ad89e33a7faee38b990@DB4PR30MB030.064d.mgd.msft.net> References: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> <50a0e2e329474ad89e33a7faee38b990@DB4PR30MB030.064d.mgd.msft.net> Message-ID: On Sat, Jun 18, 2016 at 12:51 PM, Simon Peyton Jones wrote: > > > But no need to look at the data type’s constructors, as deriving(Functor) > does. > Yes, that's right. I believe we've used the "derive Functor" strategy for inferring constraints simply because all generic functions (over Generic1) that we had in mind at the time were Functor-like, so that was an appropriate first solution. But I totally agree that it can be improved! Best regards, Pedro > > > Simon > > > > *From:* josepedromagalhaes at gmail.com [mailto:josepedromagalhaes at gmail.com] > *On Behalf Of *José Pedro Magalhães > *Sent:* 18 June 2016 09:16 > *To:* Simon Peyton Jones > *Cc:* Ryan Scott ; Andres Löh < > andres.loeh at gmail.com>; GHC developers > *Subject:* Re: Inferring instance constraints with DeriveAnyClass > > > > I still don't think you can do it just from the default method's type. A > typical case is the following: > > > > class C a where > > op :: a -> Int > > default op :: (Generic a, GC (Rep a)) => a -> Int > > > > When giving an instance C [a], you might well find out that you need C a > =>, but this is not something > > you can see in the type of the default method; it follows only after the > expansion of Rep [a] and resolving > > the GC constraint a number of times. > > > > > > Best regards, > > Pedro > > > > On Fri, Jun 17, 2016 at 12:43 PM, Simon Peyton Jones < > simonpj at microsoft.com> wrote: > > | My question is then: why does DeriveAnyClass take the bizarre approach > | of co-opting the DeriveFunctor algorithm? Andres, you originally > | proposed this in #7346 [2], but I don't quite understand why you > | wanted to do it this way. Couldn't we infer the context simply from > | the contexts of the default method type signatures? > > That last suggestion makes perfect sense to me. After all, we are going > to generate an instance looking like > > instance .. => C (T a) where > op1 = > op2 = > > so all we need in ".." is enough context to satisfy the needs of > etc. > > Well, you need to take account of the class op type sig too: > > class C a where > op :: Eq a => a -> a > default op :: (Eq a, Show a) => a -> a > > We effectively define > default_op :: (Eq a, Show a) => a -> a > > Now with DeriveAnyClass for lists, we effectively get > > instance ... => C [a] where > op = default_op > > What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq [a] > (because that's op's instantiated type. So Show a is all we need in the > end. > > Simon > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Sun Jun 19 02:07:14 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sat, 18 Jun 2016 19:07:14 -0700 Subject: Optimizing "counting" GADTs In-Reply-To: References: Message-ID: David, Carter, It would be nice to use pattern synonyms for this task but they do not work quite as expected as they don't cause type refinement. I quickly assembled this note to explain why. http://mpickering.github.io/posts/2016-06-18-why-no-refinement.html Matt On Fri, May 27, 2016 at 4:50 AM, David Feuer wrote: > Scratch that. I think you might be right. > > On May 25, 2016 8:40 PM, "David Feuer" wrote: >> >> Partially. Unfortunately, bidirectional pattern synonyms tie the types of >> the pattern synonyms to the types of the smart constructors for no good >> reason, making them (currently) inappropriate. But fixing that problem would >> offer one way to this optimization, I think. >> >> On May 25, 2016 8:37 PM, "Carter Schonwald" >> wrote: >> >> could this be simulated/modeled with pattern synonyms? >> >> On Wed, May 25, 2016 at 7:51 PM, David Feuer >> wrote: >>> >>> I've started a wiki page, >>> https://ghc.haskell.org/trac/ghc/wiki/OptimizeCountingGADTs , to consider >>> optimizing GADTs that look like natural numbers but that possibly have >>> "heavy zeros". Please take a look. >>> >>> >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> >> > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From david.feuer at gmail.com Sun Jun 19 02:47:54 2016 From: david.feuer at gmail.com (David Feuer) Date: Sat, 18 Jun 2016 22:47:54 -0400 Subject: Optimizing "counting" GADTs In-Reply-To: References: Message-ID: I would think the provided equalities could be constructed in a view pattern, possibly using unsafeCoerce. Dictionaries are harder to come by, but reflection might be an option. My two biggest gripes about pattern synonyms are really 1. The constraints for "constructor" application are forced to be much tighter than necessary. This is very sad because there doesn't seem to be anything inherently difficult about fixing it--just allow the user to specify the desired type signature for the synonym used as a constructor. 2. The exhaustivity check doesn't work yet. On Jun 18, 2016 10:07 PM, "Matthew Pickering" wrote: > David, Carter, > > It would be nice to use pattern synonyms for this task but they do not > work quite as expected as they don't cause type refinement. > > I quickly assembled this note to explain why. > > http://mpickering.github.io/posts/2016-06-18-why-no-refinement.html > > Matt > > On Fri, May 27, 2016 at 4:50 AM, David Feuer > wrote: > > Scratch that. I think you might be right. > > > > On May 25, 2016 8:40 PM, "David Feuer" wrote: > >> > >> Partially. Unfortunately, bidirectional pattern synonyms tie the types > of > >> the pattern synonyms to the types of the smart constructors for no good > >> reason, making them (currently) inappropriate. But fixing that problem > would > >> offer one way to this optimization, I think. > >> > >> On May 25, 2016 8:37 PM, "Carter Schonwald" > > >> wrote: > >> > >> could this be simulated/modeled with pattern synonyms? > >> > >> On Wed, May 25, 2016 at 7:51 PM, David Feuer > >> wrote: > >>> > >>> I've started a wiki page, > >>> https://ghc.haskell.org/trac/ghc/wiki/OptimizeCountingGADTs , to > consider > >>> optimizing GADTs that look like natural numbers but that possibly have > >>> "heavy zeros". Please take a look. > >>> > >>> > >>> _______________________________________________ > >>> ghc-devs mailing list > >>> ghc-devs at haskell.org > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > >>> > >> > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Sun Jun 19 03:21:24 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sat, 18 Jun 2016 20:21:24 -0700 Subject: Optimizing "counting" GADTs In-Reply-To: References: Message-ID: <1466304951-sup-6189@sabre> Excerpts from David Feuer's message of 2016-06-18 19:47:54 -0700: > I would think the provided equalities could be constructed in a view > pattern, possibly using unsafeCoerce. Yes, this does work. {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE GADTs #-} {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} module GhostBuster where import GHC.TypeLits import Unsafe.Coerce newtype Vec a (n :: Nat) = Vec { unVec :: [a] } -- "Almost" Vec GADT, but the inside is a Vec -- (so only the top-level is unfolded.) data Vec' a (n :: Nat) where VNil' :: Vec' a 0 VCons' :: a -> Vec a n -> Vec' a (n + 1) upVec :: Vec a n -> Vec' a n upVec (Vec []) = unsafeCoerce VNil' upVec (Vec (x:xs)) = unsafeCoerce (VCons' x (Vec xs)) pattern VNil :: () => (n ~ 0) => Vec a n pattern VNil <- (upVec -> VNil') where VNil = Vec [] pattern VCons :: () => ((n + 1) ~ n') => a -> Vec a n -> Vec a n' pattern VCons x xs <- (upVec -> VCons' x xs) where VCons x (Vec xs) = Vec (x : xs) headVec :: Vec a (n + 1) -> a headVec (VCons x _) = x mapVec :: (a -> b) -> Vec a n -> Vec b n mapVec f VNil = (VNil :: Vec a 0) mapVec f (VCons x xs) = VCons (f x) (mapVec f xs) > Dictionaries are harder to come by, > but reflection might be an option. If I understand correctly, even if you have a Typeable dictionary you don't necessarily have a way of constructing the other dictionaries that are available at that type. Maybe that is something worth fixing. Edward From matthewtpickering at gmail.com Sun Jun 19 05:11:26 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sat, 18 Jun 2016 22:11:26 -0700 Subject: Optimizing "counting" GADTs In-Reply-To: <1466304951-sup-6189@sabre> References: <1466304951-sup-6189@sabre> Message-ID: Great stuff guys! I updated the post with your code. David, you raise two valid points. I don't have anything else to add to them at this time but it is stuff that I think about. On Sat, Jun 18, 2016 at 8:21 PM, Edward Z. Yang wrote: > Excerpts from David Feuer's message of 2016-06-18 19:47:54 -0700: >> I would think the provided equalities could be constructed in a view >> pattern, possibly using unsafeCoerce. > > Yes, this does work. > > {-# LANGUAGE KindSignatures #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE PatternSynonyms #-} > {-# LANGUAGE ViewPatterns #-} > {-# LANGUAGE TypeOperators #-} > {-# LANGUAGE GADTs #-} > {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} > module GhostBuster where > > import GHC.TypeLits > import Unsafe.Coerce > > newtype Vec a (n :: Nat) = Vec { unVec :: [a] } > > -- "Almost" Vec GADT, but the inside is a Vec > -- (so only the top-level is unfolded.) > data Vec' a (n :: Nat) where > VNil' :: Vec' a 0 > VCons' :: a -> Vec a n -> Vec' a (n + 1) > > upVec :: Vec a n -> Vec' a n > upVec (Vec []) = unsafeCoerce VNil' > upVec (Vec (x:xs)) = unsafeCoerce (VCons' x (Vec xs)) > > pattern VNil :: () => (n ~ 0) => Vec a n > pattern VNil <- (upVec -> VNil') where > VNil = Vec [] > > pattern VCons :: () => ((n + 1) ~ n') => a -> Vec a n -> Vec a n' > pattern VCons x xs <- (upVec -> VCons' x xs) where > VCons x (Vec xs) = Vec (x : xs) > > headVec :: Vec a (n + 1) -> a > headVec (VCons x _) = x > > mapVec :: (a -> b) -> Vec a n -> Vec b n > mapVec f VNil = (VNil :: Vec a 0) > mapVec f (VCons x xs) = VCons (f x) (mapVec f xs) > >> Dictionaries are harder to come by, >> but reflection might be an option. > > If I understand correctly, even if you have a Typeable dictionary you > don't necessarily have a way of constructing the other dictionaries > that are available at that type. Maybe that is something worth fixing. > > Edward From ben at smart-cactus.org Sun Jun 19 08:27:55 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Sun, 19 Jun 2016 10:27:55 +0200 Subject: Optimizing "counting" GADTs In-Reply-To: <1466304951-sup-6189@sabre> References: <1466304951-sup-6189@sabre> Message-ID: <87inx5r3as.fsf@smart-cactus.org> "Edward Z. Yang" writes: snip >> Dictionaries are harder to come by, >> but reflection might be an option. > > If I understand correctly, even if you have a Typeable dictionary you > don't necessarily have a way of constructing the other dictionaries > that are available at that type. Maybe that is something worth fixing. > Right; a Typeable dictionary gives you nothing more than the identity of the type. You cannot get any further dictionaries from it. Honestly fixing this seems quite non-trivial (essentially requiring that you construct a symbol name for the desired dictionary and do a symbol table lookup to find it, hoping that the linker didn't decide to drop it due to being unused). Moreover, it seems possible that providing this ability may have consequences on parametricity. Reflection already comes dangerously close to compromising this property; we are saved only by the fact that a Typeable constraint is needed to request a representation. I'd imagine that allowing the user to produce arbitrary dictionaries from a representation may pose similar issues. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From ben at smart-cactus.org Sun Jun 19 08:33:53 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Sun, 19 Jun 2016 10:33:53 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: <87mvml5yfg.fsf@smart-cactus.org> <87y46548ea.fsf@smart-cactus.org> Message-ID: <87fus9r30u.fsf@smart-cactus.org> Harendra Kumar writes: > Thanks Ben! I have my responses inline below. > No worries! > On 16 June 2016 at 18:07, Ben Gamari wrote: > >> For the record, I have also struggled with register spilling issues in >> the past. See, for instance, #10012, which describes a behavior which >> arises from the C-- sinking pass's unwillingness to duplicate code >> across branches. While in general it's good to avoid the code bloat that >> this duplication implies, in the case shown in that ticket duplicating >> the computation would be significantly less code than the bloat from >> spilling the needed results. >> > > Not sure if this is possible but when unsure we can try both and compare if > the duplication results in significantly more code than no duplication and > make a decision based on that. Though that will slow down the compilation. > Maybe we can bundle slower passes in something like -O3, meaning it will be > slow and may or may not provide better results? > Indeed this would be one option although I suspect we can do better. I have discussed the problem with a few people and have some ideas on how to proceed. Unfortunately I've been suffering from a chronic lack of time recently. snip >> Very interesting, thanks for writing this down! Indeed if these checks >> really are redundant then we should try to avoid them. Do you have any >> code you could share that demosntrates this? >> > snip > > I have the code to produce this CMM, I can commit it on a branch and leave > it in the github repository so that we can use it for fixing. > Indeed it would be great if you could provide the program that produced this code. >> It would be great to open Trac tickets to track some of the optimization >> > > Will do. > Thanks! >> >> Furthermore, there are a few annoying impedance mismatches between Cmm >> and LLVM's representation. This can be seen in our treatment of proc >> points: when we need to take the address of a block within a function >> LLVM requires that we break the block into a separate procedure, hiding >> many potential optimizations from the optimizer. This was discussed >> further on this list earlier this year [2]. It would be great to >> eliminate proc-point splitting but doing so will almost certainly >> require cooperation from LLVM. >> > > It sounds like we need to continue with both for now and see how the llvm > option pans out. There is clearly no reason for a decisive tilt towards > llvm in near future. > I agree. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From david.feuer at gmail.com Sun Jun 19 14:06:12 2016 From: david.feuer at gmail.com (David Feuer) Date: Sun, 19 Jun 2016 10:06:12 -0400 Subject: Optimizing "counting" GADTs In-Reply-To: <87inx5r3as.fsf@smart-cactus.org> References: <1466304951-sup-6189@sabre> <87inx5r3as.fsf@smart-cactus.org> Message-ID: I meant reflection in the sense of the reflection package. Sorry for the confusion. On Jun 19, 2016 4:28 AM, "Ben Gamari" wrote: > "Edward Z. Yang" writes: > > snip > > >> Dictionaries are harder to come by, > >> but reflection might be an option. > > > > If I understand correctly, even if you have a Typeable dictionary you > > don't necessarily have a way of constructing the other dictionaries > > that are available at that type. Maybe that is something worth fixing. > > > Right; a Typeable dictionary gives you nothing more than the identity of > the type. You cannot get any further dictionaries from it. Honestly > fixing this seems quite non-trivial (essentially requiring that you > construct a symbol name for the desired dictionary and do a symbol table > lookup to find it, hoping that the linker didn't decide to drop it due > to being unused). > > Moreover, it seems possible that providing this ability may have > consequences on parametricity. Reflection already comes dangerously > close to compromising this property; we are saved only by the fact that > a Typeable constraint is needed to request a representation. I'd imagine > that allowing the user to produce arbitrary dictionaries from a > representation may pose similar issues. > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jun 19 15:59:48 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 19 Jun 2016 11:59:48 -0400 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: <87mvml5yfg.fsf@smart-cactus.org> Message-ID: Agreed. There's also some other mismatches between ghc and llvm in a few fun / interesting ways! There's a lot of room for improvement in both code gens, but there's also a lot of room to improve the ease of experimenting with improvements. Eg we don't have a peephole pass per target, so those get hacked into the pretty printing code last time I checked On Thursday, June 16, 2016, Ben Gamari > wrote: > > Ccing David Spitzenberg, who has thought about proc-point splitting, which > is relevant for reasons that we will see below. > > > Harendra Kumar writes: > > > On 16 June 2016 at 13:59, Ben Gamari wrote: > >> > >> It actually came to my attention while researching this that the > >> -fregs-graph flag is currently silently ignored [2]. Unfortunately this > >> means you'll need to build a new compiler if you want to try using it. > > > > Yes I did try -fregs-graph and -fregs-iterative both. To debug why > nothing > > changed I had to compare the executables produced with and without the > > flags and found them identical. A note in the manual could have saved me > > some time since that's the first place to go for help. I was wondering > if I > > am making a mistake in the build and if it is not being rebuilt > > properly. Your note confirms my observation, it indeed does not change > > anything. > > > Indeed; I've opened D2335 [1] to reenable -fregs-graph and add an > appropriate note to the users guide. > > >> 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. > > > > Yes, I can try that. In fact I was going in that direction and then > stopped > > to look at what llvm does. llvm gave me impressive results in some cases > > though not so great in others. I compared the code generated by llvm and > it > > perhaps did a better job in theory (used fewer instructions) but due to > > more spilling the end result was pretty similar. > > > For the record, I have also struggled with register spilling issues in > the past. See, for instance, #10012, which describes a behavior which > arises from the C-- sinking pass's unwillingness to duplicate code > across branches. While in general it's good to avoid the code bloat that > this duplication implies, in the case shown in that ticket duplicating > the computation would be significantly less code than the bloat from > spilling the needed results. > > > But I found a few interesting optimizations that llvm did. For example, > > there was a heap adjustment and check in the looping path which was > > redundant and was readjusted in the loop itself without use. LLVM either > > removed the redundant _adjustments_ in the loop or moved them out of the > > loop. But it did not remove the corresponding heap _checks_. That makes > me > > wonder if the redundant heap checks can also be moved or removed. If we > can > > do some sort of loop analysis at the CMM level itself and avoid or remove > > the redundant heap adjustments as well as checks or at least float them > out > > of the cycle wherever possible. That sort of optimization can make a > > significant difference to my case at least. Since we are explicitly aware > > of the heap at the CMM level there may be an opportunity to do better > than > > llvm if we optimize the generated CMM or the generation of CMM itself. > > > Very interesting, thanks for writing this down! Indeed if these checks > really are redundant then we should try to avoid them. Do you have any > code you could share that demosntrates this? > > It would be great to open Trac tickets to track some of the optimization > opportunities that you noted we may be missing. Trac tickets are far > easier to track over longer durations than mailing list conversations, > which tend to get lost in the noise after a few weeks pass. > > > A thought that came to my mind was whether we should focus on getting > > better code out of the llvm backend or the native code generator. LLVM > > seems pretty good at the specialized task of code generation and low > level > > optimization, it is well funded, widely used and has a big community > > support. That allows us to leverage that huge effort and take advantage > of > > the new developments. Does it make sense to outsource the code generation > > and low level optimization tasks to llvm and ghc focussing on higher > level > > optimizations which are harder to do at the llvm level? What are the > > downsides of using llvm exclusively in future? > > > > There is indeed a question of where we wish to focus our optimization > efforts. However, I think using LLVM exclusively would be a mistake. > LLVM is a rather large dependency that has in the past been rather > difficult to track (this is why we now only target one LLVM release in a > given GHC release). Moreover, it's significantly slower than our > existing native code generator. There are a number of reasons for this, > some of which are fixable. For instance, we currently make no effort to > tell > LLVM which passes are worth running and which we've handled; this is > something which should be fixed but will require a rather significant > investment by someone to determine how GHC's and LLVM's passes overlap, > how they interact, and generally which are helpful (see GHC #11295). > > Furthermore, there are a few annoying impedance mismatches between Cmm > and LLVM's representation. This can be seen in our treatment of proc > points: when we need to take the address of a block within a function > LLVM requires that we break the block into a separate procedure, hiding > many potential optimizations from the optimizer. This was discussed > further on this list earlier this year [2]. It would be great to > eliminate proc-point splitting but doing so will almost certainly > require cooperation from LLVM. > > Cheers, > > - Ben > > > [1] https://phabricator.haskell.org/D2335 > [2] https://mail.haskell.org/pipermail/ghc-devs/2015-November/010535.html > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Sun Jun 19 19:08:09 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Sun, 19 Jun 2016 19:08:09 +0000 Subject: Simon's email classified as spam Message-ID: <436234deb9584094820a5dc045276315@DB4PR30MB030.064d.mgd.msft.net> Dear GHC devs/users This is another test to see if email from me, relayed via Haskell.org, ends up in your spam folder. Gershom thinks he’s fixed it (below). Can I trespass on your patience once more? Just let me know if this email ends up in your inbox or spam. Can you cc John and Gershom (but perhaps not everyone else)? Thanks Simon | From: Gershom B [mailto:gershomb at gmail.com] | Sent: 18 June 2016 18:53 | To: Simon Peyton Jones ; John Wiegley | | Cc: Michael Burge | Subject: Re: FW: CMM-to-SAM: Register allocation weirdness | | Simon — I just found two possible sources of the problem (first: the top | level config didn’t take hold due to other errors when updating — fixed that, | and second, it might be possible the top level config isn’t retroactively | applied to all lists — so i added the config to the relevant lists directly). | | I think if you try one more time it might work (fingers crossed). -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Sun Jun 19 20:44:56 2016 From: gershomb at gmail.com (Gershom B) Date: Sun, 19 Jun 2016 16:44:56 -0400 Subject: Simon's email classified as spam In-Reply-To: <436234deb9584094820a5dc045276315@DB4PR30MB030.064d.mgd.msft.net> References: <436234deb9584094820a5dc045276315@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Dear all, thanks for the many responses. It appears that this is now fixed. (no need to send more). Cheers, Gershom On June 19, 2016 at 3:08:28 PM, Simon Peyton Jones via Glasgow-haskell-users (glasgow-haskell-users at haskell.org) wrote: > Dear GHC devs/users > This is another test to see if email from me, relayed via Haskell.org, ends up in your spam > folder. Gershom thinks he’s fixed it (below). Can I trespass on your patience once more? > Just let me know if this email ends up in your inbox or spam. Can you cc John and Gershom (but > perhaps not everyone else)? Thanks > Simon > > > | From: Gershom B [mailto:gershomb at gmail.com] > > | Sent: 18 June 2016 18:53 > > | To: Simon Peyton Jones ; John Wiegley > > | > > | Cc: Michael Burge > > | Subject: Re: FW: CMM-to-SAM: Register allocation weirdness > > | > > | Simon — I just found two possible sources of the problem (first: the top > > | level config didn’t take hold due to other errors when updating — fixed that, > > | and second, it might be possible the top level config isn’t retroactively > > | applied to all lists — so i added the config to the relevant lists directly). > > | > > | I think if you try one more time it might work (fingers crossed). > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From andres.loeh at gmail.com Tue Jun 21 11:23:43 2016 From: andres.loeh at gmail.com (=?UTF-8?Q?Andres_L=C3=B6h?=) Date: Tue, 21 Jun 2016 13:23:43 +0200 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: References: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> <50a0e2e329474ad89e33a7faee38b990@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Sorry for the late reply. I think the reason I proposed to reuse the algorithm for Functor was that (A) as Pedro says, it was the class most closely resembling the classes we wanted to write at the time, and (B) I almost certainly was not at all aware that there is special magic in the code for contravariant arguments. In general, I'm not overly eager to try to be too clever in inferring the right instance constraints. I think standalone deriving should be used in anything but the most straight-forward scenarios. If there is a simple and easy-to-specify way to infer the simple cases properly though, I am certainly not opposed to it. Cheers, Andres On Sat, Jun 18, 2016 at 1:55 PM, José Pedro Magalhães wrote: > > > On Sat, Jun 18, 2016 at 12:51 PM, Simon Peyton Jones > wrote: >> >> >> >> But no need to look at the data type’s constructors, as deriving(Functor) >> does. > > > Yes, that's right. > > I believe we've used the "derive Functor" strategy for inferring constraints > simply because all generic functions (over Generic1) that we had in mind at > the time were Functor-like, so that was an appropriate first solution. But I > totally agree that it can be improved! > > > Best regards, > Pedro > >> >> >> >> Simon >> >> >> >> From: josepedromagalhaes at gmail.com [mailto:josepedromagalhaes at gmail.com] >> On Behalf Of José Pedro Magalhães >> Sent: 18 June 2016 09:16 >> To: Simon Peyton Jones >> Cc: Ryan Scott ; Andres Löh >> ; GHC developers >> Subject: Re: Inferring instance constraints with DeriveAnyClass >> >> >> >> I still don't think you can do it just from the default method's type. A >> typical case is the following: >> >> >> >> class C a where >> >> op :: a -> Int >> >> default op :: (Generic a, GC (Rep a)) => a -> Int >> >> >> >> When giving an instance C [a], you might well find out that you need C a >> =>, but this is not something >> >> you can see in the type of the default method; it follows only after the >> expansion of Rep [a] and resolving >> >> the GC constraint a number of times. >> >> >> >> >> >> Best regards, >> >> Pedro >> >> >> >> On Fri, Jun 17, 2016 at 12:43 PM, Simon Peyton Jones >> wrote: >> >> | My question is then: why does DeriveAnyClass take the bizarre approach >> | of co-opting the DeriveFunctor algorithm? Andres, you originally >> | proposed this in #7346 [2], but I don't quite understand why you >> | wanted to do it this way. Couldn't we infer the context simply from >> | the contexts of the default method type signatures? >> >> That last suggestion makes perfect sense to me. After all, we are going >> to generate an instance looking like >> >> instance .. => C (T a) where >> op1 = >> op2 = >> >> so all we need in ".." is enough context to satisfy the needs of >> etc. >> >> Well, you need to take account of the class op type sig too: >> >> class C a where >> op :: Eq a => a -> a >> default op :: (Eq a, Show a) => a -> a >> >> We effectively define >> default_op :: (Eq a, Show a) => a -> a >> >> Now with DeriveAnyClass for lists, we effectively get >> >> instance ... => C [a] where >> op = default_op >> >> What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq [a] >> (because that's op's instantiated type. So Show a is all we need in the >> end. >> >> Simon >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> > > From simonpj at microsoft.com Tue Jun 21 13:51:40 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 21 Jun 2016 13:51:40 +0000 Subject: Inferring instance constraints with DeriveAnyClass In-Reply-To: References: <1dfe236f013d439f9c4101508ac23c00@DB4PR30MB030.064d.mgd.msft.net> <50a0e2e329474ad89e33a7faee38b990@DB4PR30MB030.064d.mgd.msft.net> Message-ID: | forward scenarios. If there is a simple and easy-to-specify way to | infer the simple cases properly though, I am certainly not opposed to | it. I think there is a simple easy-to-specify way to infer /all/ cases! Simon | -----Original Message----- | From: Andres Löh [mailto:andres.loeh at gmail.com] | Sent: 21 June 2016 12:24 | To: Pedro Magalhães (dreixel at gmail.com) | Cc: Simon Peyton Jones ; Ryan Scott | ; GHC developers | Subject: Re: Inferring instance constraints with DeriveAnyClass | | Sorry for the late reply. | | I think the reason I proposed to reuse the algorithm for Functor was | that (A) as Pedro says, it was the class most closely resembling the | classes we wanted to write at the time, and (B) I almost certainly was | not at all aware that there is special magic in the code for | contravariant arguments. In general, I'm not overly eager to try to be | too clever in inferring the right instance constraints. I think | standalone deriving should be used in anything but the most straight- | forward scenarios. If there is a simple and easy-to-specify way to | infer the simple cases properly though, I am certainly not opposed to | it. | | Cheers, | Andres | | On Sat, Jun 18, 2016 at 1:55 PM, José Pedro Magalhães | wrote: | > | > | > On Sat, Jun 18, 2016 at 12:51 PM, Simon Peyton Jones | > | > wrote: | >> | >> | >> | >> But no need to look at the data type’s constructors, as | >> deriving(Functor) does. | > | > | > Yes, that's right. | > | > I believe we've used the "derive Functor" strategy for inferring | > constraints simply because all generic functions (over Generic1) | that | > we had in mind at the time were Functor-like, so that was an | > appropriate first solution. But I totally agree that it can be | improved! | > | > | > Best regards, | > Pedro | > | >> | >> | >> | >> Simon | >> | >> | >> | >> From: josepedromagalhaes at gmail.com | >> [mailto:josepedromagalhaes at gmail.com] | >> On Behalf Of José Pedro Magalhães | >> Sent: 18 June 2016 09:16 | >> To: Simon Peyton Jones | >> Cc: Ryan Scott ; Andres Löh | >> ; GHC developers | >> Subject: Re: Inferring instance constraints with DeriveAnyClass | >> | >> | >> | >> I still don't think you can do it just from the default method's | >> type. A typical case is the following: | >> | >> | >> | >> class C a where | >> | >> op :: a -> Int | >> | >> default op :: (Generic a, GC (Rep a)) => a -> Int | >> | >> | >> | >> When giving an instance C [a], you might well find out that you | need | >> C a =>, but this is not something | >> | >> you can see in the type of the default method; it follows only | after | >> the expansion of Rep [a] and resolving | >> | >> the GC constraint a number of times. | >> | >> | >> | >> | >> | >> Best regards, | >> | >> Pedro | >> | >> | >> | >> On Fri, Jun 17, 2016 at 12:43 PM, Simon Peyton Jones | >> wrote: | >> | >> | My question is then: why does DeriveAnyClass take the bizarre | >> | approach of co-opting the DeriveFunctor algorithm? Andres, you | >> | originally proposed this in #7346 [2], but I don't quite | understand | >> | why you wanted to do it this way. Couldn't we infer the context | >> | simply from the contexts of the default method type signatures? | >> | >> That last suggestion makes perfect sense to me. After all, we are | >> going to generate an instance looking like | >> | >> instance .. => C (T a) where | >> op1 = | >> op2 = | >> | >> so all we need in ".." is enough context to satisfy the needs of | >> etc. | >> | >> Well, you need to take account of the class op type sig too: | >> | >> class C a where | >> op :: Eq a => a -> a | >> default op :: (Eq a, Show a) => a -> a | >> | >> We effectively define | >> default_op :: (Eq a, Show a) => a -> a | >> | >> Now with DeriveAnyClass for lists, we effectively get | >> | >> instance ... => C [a] where | >> op = default_op | >> | >> What is ..? Well, we need (Eq [a], Show [a]); but we are given Eq | >> [a] (because that's op's instantiated type. So Show a is all we | need | >> in the end. | >> | >> Simon | >> _______________________________________________ | >> ghc-devs mailing list | >> ghc-devs at haskell.org | >> | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail. | >> haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7c | >> | simonpj%40064d.mgd.microsoft.com%7c0087fcdf47ce4b70daa908d399c68207%7 | >> | c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=gmMJ4kcKnMS2HQghLI3HKBqHV | >> FzBmk4FFJa%2bUY%2bBv7c%3d | >> | >> | > | > From marlowsd at gmail.com Wed Jun 22 08:51:12 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 09:51:12 +0100 Subject: Require -fexternal-interpreter support for future TH changes? Message-ID: *Background* A few months ago I added -fexternal-interpreter to GHC: - docs: http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi When -fexternal-interpreter is used, GHC runs interpreted code in a separate subprocess, and communicates with it using binary messages over a pipe. -fexternal-interpreter currently implements all of TH, quasi-quoting, annotations, and all the GHCi features except for some features of the debugger. It is also now implemented on Windows, thanks to Tamar Christina. *Proposal* I'd like to propose that going forward we commit to maintaining full support for -fexternal-interpreter, with a view to making it the default. Why? - -fexternal-interpreter will be a prerequisite for GHCJS support, so maintaining full support for TH in -fexternal-interpreter will ensure that everything that works with GHC works with GHCJS. - We will be able to make simplifications in GHC and the build system once -fexternal-interpreter is the default, because when compiling with -prof or -dynamic we won't have to compile things twice any more. - Ultimately we don't want to have two ways of doing everything, because that's harder to maintain. How? - I'll make all the TH and quasi-quoting tests run with and without -fexternal-interpreter, so it will break validate if one of these fails. *Why now?* There are some TH changes in the pipeline that will need special attention to work with -fexternal-interpreter. e.g. https://phabricator.haskell.org/D2286 and https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so I'd like to raise it now so we can keep the issue in mind. Cheers Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 22 10:37:21 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 22 Jun 2016 10:37:21 +0000 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: Message-ID: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> I’m ok with this. It would certainly be great not to support TWO mechanisms indefinitely. What are the disadvantages to committing to this path? Would anyone even notice? There are a lot of moving parts to the implementation, and I for one am utterly ignorant of how it all works. I would love to see an implementation overview, either somewhere in the code or on a wiki page. Things like: · How, when, and where in the compiler is the separate process started? · How do the compiler and server communicate? Unix pipes? Is it the same on Windows and Unix? · What is serialised, when, and how? For example, GHC has some TH code to run. Do we send a syntax tree? Or compile to bytecode and send that? Or what? · How are external references managed. E.g. if the code to be run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers to “a library implementing a message type…” but I don’t know what that library is called or where it lives. Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Marlow Sent: 22 June 2016 09:51 To: ghc-devs at haskell.org Subject: Require -fexternal-interpreter support for future TH changes? Background A few months ago I added -fexternal-interpreter to GHC: * docs: http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter * wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi When -fexternal-interpreter is used, GHC runs interpreted code in a separate subprocess, and communicates with it using binary messages over a pipe. -fexternal-interpreter currently implements all of TH, quasi-quoting, annotations, and all the GHCi features except for some features of the debugger. It is also now implemented on Windows, thanks to Tamar Christina. Proposal I'd like to propose that going forward we commit to maintaining full support for -fexternal-interpreter, with a view to making it the default. Why? * -fexternal-interpreter will be a prerequisite for GHCJS support, so maintaining full support for TH in -fexternal-interpreter will ensure that everything that works with GHC works with GHCJS. * We will be able to make simplifications in GHC and the build system once -fexternal-interpreter is the default, because when compiling with -prof or -dynamic we won't have to compile things twice any more. * Ultimately we don't want to have two ways of doing everything, because that's harder to maintain. How? * I'll make all the TH and quasi-quoting tests run with and without -fexternal-interpreter, so it will break validate if one of these fails. Why now? There are some TH changes in the pipeline that will need special attention to work with -fexternal-interpreter. e.g. https://phabricator.haskell.org/D2286 and https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so I'd like to raise it now so we can keep the issue in mind. Cheers Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Wed Jun 22 10:50:11 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 11:50:11 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> Message-ID: On 22 June 2016 at 11:37, Simon Peyton Jones wrote: > I’m ok with this. *It would certainly be great not to support TWO > mechanisms indefinitely*. > > > > What are the disadvantages to committing to this path? Would anyone even > notice? > Yes, people who are making changes to TH will need to ensure that their changes work with -fexternal-interpreter. In some cases that might mean extra work, e.g. if we do TemplateHaskell/Introspective then potentially the whole of HsSyn needs to be binary serializable. That worries me quite a lot - THSyn is big but tractable, Generic deriving handled the generation of the binary instances easily enough, but HsSyn is another matter entirely. > There are a lot of moving parts to the implementation, and I for one am > utterly ignorant of how it all works. I would love to see an > implementation overview, either somewhere in the code or on a wiki page. > Things like: > > · How, when, and where in the compiler is the separate process > started? > > · How do the compiler and server communicate? Unix pipes? Is it > the same on Windows and Unix? > > · What is serialised, when, and how? For example, GHC has some > TH code to run. Do we send a syntax tree? Or compile to bytecode and send > that? Or what? > > · How are external references managed. E.g. if the code to be > run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. > > I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers > to “a library implementing a message type…” but I don’t know what that > library is called or where it lives. > Yes, we should really have a page in the commentary with an overview of the pieces and the main implementation strategy. I'll write one. Cheers Simon > > > Thanks > > > > Simon > > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Simon > Marlow > *Sent:* 22 June 2016 09:51 > *To:* ghc-devs at haskell.org > *Subject:* Require -fexternal-interpreter support for future TH changes? > > > > *Background* > > A few months ago I added -fexternal-interpreter to GHC: > > - docs: > http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > > - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > > When -fexternal-interpreter is used, GHC runs interpreted code in a > separate subprocess, and communicates with it using binary messages over a > pipe. > > -fexternal-interpreter currently implements all of TH, quasi-quoting, > annotations, and all the GHCi features except for some features of the > debugger. It is also now implemented on Windows, thanks to Tamar Christina. > > *Proposal* > > I'd like to propose that going forward we commit to maintaining full > support for -fexternal-interpreter, with a view to making it the default. > > Why? > > - -fexternal-interpreter will be a prerequisite for GHCJS support, so > maintaining full support for TH in -fexternal-interpreter will ensure that > everything that works with GHC works with GHCJS. > - We will be able to make simplifications in GHC and the build system > once -fexternal-interpreter is the default, because when compiling with > -prof or -dynamic we won't have to compile things twice any more. > - Ultimately we don't want to have two ways of doing everything, > because that's harder to maintain. > > How? > > - I'll make all the TH and quasi-quoting tests run with and without > -fexternal-interpreter, so it will break validate if one of these fails. > > *Why now?* > > There are some TH changes in the pipeline that will need special attention > to work with -fexternal-interpreter. e.g. > https://phabricator.haskell.org/D2286 and > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so > I'd like to raise it now so we can keep the issue in mind. > > > > Cheers > > Simon > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Wed Jun 22 11:31:50 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 12:31:50 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> Message-ID: How's this? https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/ExternalInterpreter I don't want to go into too much detail in the wiki, because details are more likely to stay current if they're in Notes in the code. There are already a few Notes (e.g. https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/ghci/GHCi.hs;619958832cbe11096cae3dac9a0a7a5591163a00$86) but if anything is confusing I'll happily add more Notes. Cheers Simon On 22 June 2016 at 11:50, Simon Marlow wrote: > On 22 June 2016 at 11:37, Simon Peyton Jones > wrote: > >> I’m ok with this. *It would certainly be great not to support TWO >> mechanisms indefinitely*. >> >> >> >> What are the disadvantages to committing to this path? Would anyone even >> notice? >> > > Yes, people who are making changes to TH will need to ensure that their > changes work with -fexternal-interpreter. In some cases that might mean > extra work, e.g. if we do TemplateHaskell/Introspective > > then potentially the whole of HsSyn needs to be binary serializable. That > worries me quite a lot - THSyn is big but tractable, Generic deriving > handled the generation of the binary instances easily enough, but HsSyn is > another matter entirely. > > >> There are a lot of moving parts to the implementation, and I for one am >> utterly ignorant of how it all works. I would love to see an >> implementation overview, either somewhere in the code or on a wiki page. >> Things like: >> >> · How, when, and where in the compiler is the separate process >> started? >> >> · How do the compiler and server communicate? Unix pipes? Is it >> the same on Windows and Unix? >> >> · What is serialised, when, and how? For example, GHC has some >> TH code to run. Do we send a syntax tree? Or compile to bytecode and send >> that? Or what? >> >> · How are external references managed. E.g. if the code to be >> run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. >> >> I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers >> to “a library implementing a message type…” but I don’t know what that >> library is called or where it lives. >> > > Yes, we should really have a page in the commentary with an overview of > the pieces and the main implementation strategy. I'll write one. > > Cheers > Simon > > >> >> >> Thanks >> >> >> >> Simon >> >> >> >> *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Simon >> Marlow >> *Sent:* 22 June 2016 09:51 >> *To:* ghc-devs at haskell.org >> *Subject:* Require -fexternal-interpreter support for future TH changes? >> >> >> >> *Background* >> >> A few months ago I added -fexternal-interpreter to GHC: >> >> - docs: >> http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter >> >> - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi >> >> When -fexternal-interpreter is used, GHC runs interpreted code in a >> separate subprocess, and communicates with it using binary messages over a >> pipe. >> >> -fexternal-interpreter currently implements all of TH, quasi-quoting, >> annotations, and all the GHCi features except for some features of the >> debugger. It is also now implemented on Windows, thanks to Tamar Christina. >> >> *Proposal* >> >> I'd like to propose that going forward we commit to maintaining full >> support for -fexternal-interpreter, with a view to making it the default. >> >> Why? >> >> - -fexternal-interpreter will be a prerequisite for GHCJS support, so >> maintaining full support for TH in -fexternal-interpreter will ensure that >> everything that works with GHC works with GHCJS. >> - We will be able to make simplifications in GHC and the build system >> once -fexternal-interpreter is the default, because when compiling with >> -prof or -dynamic we won't have to compile things twice any more. >> - Ultimately we don't want to have two ways of doing everything, >> because that's harder to maintain. >> >> How? >> >> - I'll make all the TH and quasi-quoting tests run with and without >> -fexternal-interpreter, so it will break validate if one of these fails. >> >> *Why now?* >> >> There are some TH changes in the pipeline that will need special >> attention to work with -fexternal-interpreter. e.g. >> https://phabricator.haskell.org/D2286 and >> https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so >> I'd like to raise it now so we can keep the issue in mind. >> >> >> >> Cheers >> >> Simon >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 22 12:27:02 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 22 Jun 2016 12:27:02 +0000 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> Message-ID: It’s a great start, thanks Simon From: Simon Marlow [mailto:marlowsd at gmail.com] Sent: 22 June 2016 12:32 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: Re: Require -fexternal-interpreter support for future TH changes? How's this? https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/ExternalInterpreter I don't want to go into too much detail in the wiki, because details are more likely to stay current if they're in Notes in the code. There are already a few Notes (e.g. https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/ghci/GHCi.hs;619958832cbe11096cae3dac9a0a7a5591163a00$86) but if anything is confusing I'll happily add more Notes. Cheers Simon On 22 June 2016 at 11:50, Simon Marlow > wrote: On 22 June 2016 at 11:37, Simon Peyton Jones > wrote: I’m ok with this. It would certainly be great not to support TWO mechanisms indefinitely. What are the disadvantages to committing to this path? Would anyone even notice? Yes, people who are making changes to TH will need to ensure that their changes work with -fexternal-interpreter. In some cases that might mean extra work, e.g. if we do TemplateHaskell/Introspective then potentially the whole of HsSyn needs to be binary serializable. That worries me quite a lot - THSyn is big but tractable, Generic deriving handled the generation of the binary instances easily enough, but HsSyn is another matter entirely. There are a lot of moving parts to the implementation, and I for one am utterly ignorant of how it all works. I would love to see an implementation overview, either somewhere in the code or on a wiki page. Things like: • How, when, and where in the compiler is the separate process started? • How do the compiler and server communicate? Unix pipes? Is it the same on Windows and Unix? • What is serialised, when, and how? For example, GHC has some TH code to run. Do we send a syntax tree? Or compile to bytecode and send that? Or what? • How are external references managed. E.g. if the code to be run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers to “a library implementing a message type…” but I don’t know what that library is called or where it lives. Yes, we should really have a page in the commentary with an overview of the pieces and the main implementation strategy. I'll write one. Cheers Simon Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Marlow Sent: 22 June 2016 09:51 To: ghc-devs at haskell.org Subject: Require -fexternal-interpreter support for future TH changes? Background A few months ago I added -fexternal-interpreter to GHC: * docs: http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter * wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi When -fexternal-interpreter is used, GHC runs interpreted code in a separate subprocess, and communicates with it using binary messages over a pipe. -fexternal-interpreter currently implements all of TH, quasi-quoting, annotations, and all the GHCi features except for some features of the debugger. It is also now implemented on Windows, thanks to Tamar Christina. Proposal I'd like to propose that going forward we commit to maintaining full support for -fexternal-interpreter, with a view to making it the default. Why? * -fexternal-interpreter will be a prerequisite for GHCJS support, so maintaining full support for TH in -fexternal-interpreter will ensure that everything that works with GHC works with GHCJS. * We will be able to make simplifications in GHC and the build system once -fexternal-interpreter is the default, because when compiling with -prof or -dynamic we won't have to compile things twice any more. * Ultimately we don't want to have two ways of doing everything, because that's harder to maintain. How? * I'll make all the TH and quasi-quoting tests run with and without -fexternal-interpreter, so it will break validate if one of these fails. Why now? There are some TH changes in the pipeline that will need special attention to work with -fexternal-interpreter. e.g. https://phabricator.haskell.org/D2286 and https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so I'd like to raise it now so we can keep the issue in mind. Cheers Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Wed Jun 22 13:36:03 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Wed, 22 Jun 2016 09:36:03 -0400 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> It seems there are nice advantages to this approach, and so I'm fine requiring support from TH. But here is a comment I just posted on D2286 requesting more comments in the code: --- I've just spent some time staring at GHCi/TH.hs and friends, and it's starting to make sense. Would it be possible to add some comments/Notes there? It would be great to know what is run on the client (GHC, right?) and what on the server (TH, right?). Also, why do we need a RemoteRef of an IORef? This, at first, strikes me as odd. I'm sure it makes great sense once I understand all the other moving parts, but it would be helpful to have a primer. I also find it a bit confusing that the Message type contains both messages to the server and messages from the server. For example, I would expect StartTH and Reify to live in different datatypes, because the two should never mix. Or am I horribly mistaken? --- Before we require -fexternal-interpreter (which seems to be the endgoal here), has anyone looked at performance implications? All the marshaling and unmarshaling has to take a toll. Richard On Jun 22, 2016, at 8:27 AM, Simon Peyton Jones via ghc-devs wrote: > It’s a great start, thanks > > Simon > > From: Simon Marlow [mailto:marlowsd at gmail.com] > Sent: 22 June 2016 12:32 > To: Simon Peyton Jones > Cc: ghc-devs at haskell.org > Subject: Re: Require -fexternal-interpreter support for future TH changes? > > How's this? https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/ExternalInterpreter > > I don't want to go into too much detail in the wiki, because details are more likely to stay current if they're in Notes in the code. There are already a few Notes (e.g.https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/ghci/GHCi.hs;619958832cbe11096cae3dac9a0a7a5591163a00$86) but if anything is confusing I'll happily add more Notes. > > Cheers > > Simon > > > > On 22 June 2016 at 11:50, Simon Marlow wrote: > > On 22 June 2016 at 11:37, Simon Peyton Jones wrote: > > I’m ok with this. It would certainly be great not to support TWO mechanisms indefinitely. > > What are the disadvantages to committing to this path? Would anyone even notice? > > Yes, people who are making changes to TH will need to ensure that their changes work with -fexternal-interpreter. In some cases that might mean extra work, e.g. if we do TemplateHaskell/Introspective then potentially the whole of HsSyn needs to be binary serializable. That worries me quite a lot - THSyn is big but tractable, Generic deriving handled the generation of the binary instances easily enough, but HsSyn is another matter entirely. > > There are a lot of moving parts to the implementation, and I for one am utterly ignorant of how it all works. I would love to see an implementation overview, either somewhere in the code or on a wiki page. Things like: > · How, when, and where in the compiler is the separate process started? > > · How do the compiler and server communicate? Unix pipes? Is it the same on Windows and Unix? > > · What is serialised, when, and how? For example, GHC has some TH code to run. Do we send a syntax tree? Or compile to bytecode and send that? Or what? > > · How are external references managed. E.g. if the code to be run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. > > I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers to “a library implementing a message type…” but I don’t know what that library is called or where it lives. > > Yes, we should really have a page in the commentary with an overview of the pieces and the main implementation strategy. I'll write one. > > Cheers > Simon > > > Thanks > > Simon > > From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Marlow > Sent: 22 June 2016 09:51 > To: ghc-devs at haskell.org > Subject: Require -fexternal-interpreter support for future TH changes? > > Background > > A few months ago I added -fexternal-interpreter to GHC: > > docs: http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > When -fexternal-interpreter is used, GHC runs interpreted code in a separate subprocess, and communicates with it using binary messages over a pipe. > > -fexternal-interpreter currently implements all of TH, quasi-quoting, annotations, and all the GHCi features except for some features of the debugger. It is also now implemented on Windows, thanks to Tamar Christina. > > Proposal > > I'd like to propose that going forward we commit to maintaining full support for -fexternal-interpreter, with a view to making it the default. > > Why? > -fexternal-interpreter will be a prerequisite for GHCJS support, so maintaining full support for TH in -fexternal-interpreter will ensure that everything that works with GHC works with GHCJS. > We will be able to make simplifications in GHC and the build system once -fexternal-interpreter is the default, because when compiling with -prof or -dynamic we won't have to compile things twice any more. > Ultimately we don't want to have two ways of doing everything, because that's harder to maintain. > How? > I'll make all the TH and quasi-quoting tests run with and without -fexternal-interpreter, so it will break validate if one of these fails. > Why now? > > There are some TH changes in the pipeline that will need special attention to work with -fexternal-interpreter. e.g.https://phabricator.haskell.org/D2286 and https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so I'd like to raise it now so we can keep the issue in mind. > > > > Cheers > > Simon > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Wed Jun 22 14:38:47 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 15:38:47 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> Message-ID: Thanks for the feedback Richard. It's helpful to know which parts of the implementation you found non-obvious. I will write some more Notes, but first: * On why we need a RemoteRef of an IORef - because the IORef lives on the server, so GHC has a RemoteRef to it. Did you see Note [External GHCi pointers] in compiler/ghci/GHCi.hs? Does that help? Should I xref it from somewhere else? * We probably could separate Message into two types, it's a good idea. I'll look into doing that. Cheers Simon On 22 June 2016 at 14:36, Richard Eisenberg wrote: > It seems there are nice advantages to this approach, and so I'm fine > requiring support from TH. But here is a comment I just posted on D2286 > requesting more comments in the code: > > --- > I've just spent some time staring at GHCi/TH.hs and friends, and it's > starting to make sense. Would it be possible to add some comments/Notes > there? It would be great to know what is run on the client (GHC, right?) > and what on the server (TH, right?). Also, why do we need a RemoteRef of > an IORef? This, at first, strikes me as odd. I'm sure it makes great > sense once I understand all the other moving parts, but it would be helpful > to have a primer. I also find it a bit confusing that the Message type > contains both messages to the server and messages from the server. For > example, I would expect StartTH and Reify to live in different datatypes, > because the two should never mix. Or am I horribly mistaken? > --- > > Before we require -fexternal-interpreter (which seems to be the endgoal > here), has anyone looked at performance implications? All the marshaling > and unmarshaling has to take a toll. > > Richard > > On Jun 22, 2016, at 8:27 AM, Simon Peyton Jones via ghc-devs < > ghc-devs at haskell.org> wrote: > > It’s a great start, thanks > > Simon > > *From:* Simon Marlow [mailto:marlowsd at gmail.com] > *Sent:* 22 June 2016 12:32 > *To:* Simon Peyton Jones > *Cc:* ghc-devs at haskell.org > *Subject:* Re: Require -fexternal-interpreter support for future TH > changes? > > > How's this? > https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/ExternalInterpreter > > I don't want to go into too much detail in the wiki, because details are > more likely to stay current if they're in Notes in the code. There are > already a few Notes (e.g. > https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/ghci/GHCi.hs;619958832cbe11096cae3dac9a0a7a5591163a00$86) > but if anything is confusing I'll happily add more Notes. > > Cheers > > Simon > > > > On 22 June 2016 at 11:50, Simon Marlow wrote: > > On 22 June 2016 at 11:37, Simon Peyton Jones > wrote: > > I’m ok with this. *It would certainly be great not to support TWO > mechanisms indefinitely*. > > What are the disadvantages to committing to this path? Would anyone even > notice? > > > Yes, people who are making changes to TH will need to ensure that their > changes work with -fexternal-interpreter. In some cases that might mean > extra work, e.g. if we do TemplateHaskell/Introspective > then > potentially the whole of HsSyn needs to be binary serializable. That > worries me quite a lot - THSyn is big but tractable, Generic deriving > handled the generation of the binary instances easily enough, but HsSyn is > another matter entirely. > > > There are a lot of moving parts to the implementation, and I for one am > utterly ignorant of how it all works. I would love to see an > implementation overview, either somewhere in the code or on a wiki page. > Things like: > > · How, when, and where in the compiler is the separate process > started? > > · How do the compiler and server communicate? Unix pipes? Is it > the same on Windows and Unix? > > · What is serialised, when, and how? For example, GHC has some > TH code to run. Do we send a syntax tree? Or compile to bytecode and send > that? Or what? > > · How are external references managed. E.g. if the code to be > run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. > I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers > to “a library implementing a message type…” but I don’t know what that > library is called or where it lives. > > > > Yes, we should really have a page in the commentary with an overview of > the pieces and the main implementation strategy. I'll write one. > Cheers > Simon > > > > Thanks > > Simon > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Simon > Marlow > *Sent:* 22 June 2016 09:51 > *To:* ghc-devs at haskell.org > *Subject:* Require -fexternal-interpreter support for future TH changes? > > > *Background* > > A few months ago I added -fexternal-interpreter to GHC: > > - docs: > http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > > - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > > When -fexternal-interpreter is used, GHC runs interpreted code in a > separate subprocess, and communicates with it using binary messages over a > pipe. > > -fexternal-interpreter currently implements all of TH, quasi-quoting, > annotations, and all the GHCi features except for some features of the > debugger. It is also now implemented on Windows, thanks to Tamar Christina. > > *Proposal* > > I'd like to propose that going forward we commit to maintaining full > support for -fexternal-interpreter, with a view to making it the default. > Why? > > - -fexternal-interpreter will be a prerequisite for GHCJS support, so > maintaining full support for TH in -fexternal-interpreter will ensure that > everything that works with GHC works with GHCJS. > - We will be able to make simplifications in GHC and the build system > once -fexternal-interpreter is the default, because when compiling with > -prof or -dynamic we won't have to compile things twice any more. > - Ultimately we don't want to have two ways of doing everything, > because that's harder to maintain. > > How? > > - I'll make all the TH and quasi-quoting tests run with and without > -fexternal-interpreter, so it will break validate if one of these fails. > > *Why now?* > > There are some TH changes in the pipeline that will need special attention > to work with -fexternal-interpreter. e.g. > https://phabricator.haskell.org/D2286 and > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so > I'd like to raise it now so we can keep the issue in mind. > > > > Cheers > > Simon > > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Wed Jun 22 14:40:04 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Wed, 22 Jun 2016 10:40:04 -0400 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: Message-ID: <1466605979-sup-4690@sabre> Hello Simon, I have no exception to having it be default and dropping the special case support for building profiled/dynamic so that TH works. But I don't think support for loading code in-process for GHC should be dropped, c.f. Manuel's email https://mail.haskell.org/pipermail/ghc-devs/2015-November/010491.html and also the necessity to run code in-process for typechecking plugins, etc. Edward Excerpts from Simon Marlow's message of 2016-06-22 04:51:12 -0400: > *Background* > > A few months ago I added -fexternal-interpreter to GHC: > > - docs: > http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > > When -fexternal-interpreter is used, GHC runs interpreted code in a > separate subprocess, and communicates with it using binary messages over a > pipe. > > -fexternal-interpreter currently implements all of TH, quasi-quoting, > annotations, and all the GHCi features except for some features of the > debugger. It is also now implemented on Windows, thanks to Tamar Christina. > > *Proposal* > > I'd like to propose that going forward we commit to maintaining full > support for -fexternal-interpreter, with a view to making it the default. > > Why? > > - -fexternal-interpreter will be a prerequisite for GHCJS support, so > maintaining full support for TH in -fexternal-interpreter will ensure that > everything that works with GHC works with GHCJS. > - We will be able to make simplifications in GHC and the build system > once -fexternal-interpreter is the default, because when compiling with > -prof or -dynamic we won't have to compile things twice any more. > - Ultimately we don't want to have two ways of doing everything, because > that's harder to maintain. > > How? > > - I'll make all the TH and quasi-quoting tests run with and without > -fexternal-interpreter, so it will break validate if one of these fails. > > *Why now?* > > There are some TH changes in the pipeline that will need special attention > to work with -fexternal-interpreter. e.g. > https://phabricator.haskell.org/D2286 and > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so I'd > like to raise it now so we can keep the issue in mind. > > > Cheers > > Simon From marlowsd at gmail.com Wed Jun 22 14:53:16 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 15:53:16 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: <1466605979-sup-4690@sabre> References: <1466605979-sup-4690@sabre> Message-ID: Yes - I wasn't planning on dropping support for the in-process interpreter, for that reason. I haven't thought about plugins very much, but aren't they always compiled code? We don't need an in-process interpreter for those, but we do need in-process linking. Maybe that doesn't simplify things much. Cheers Simon On 22 June 2016 at 15:40, Edward Z. Yang wrote: > Hello Simon, > > I have no exception to having it be default and dropping the special > case support for building profiled/dynamic so that TH works. But > I don't think support for loading code in-process for GHC should be > dropped, > c.f. Manuel's email > https://mail.haskell.org/pipermail/ghc-devs/2015-November/010491.html > and also the necessity to run code in-process for typechecking plugins, > etc. > > Edward > > Excerpts from Simon Marlow's message of 2016-06-22 04:51:12 -0400: > > *Background* > > > > A few months ago I added -fexternal-interpreter to GHC: > > > > - docs: > > > http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > > - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > > > > When -fexternal-interpreter is used, GHC runs interpreted code in a > > separate subprocess, and communicates with it using binary messages over > a > > pipe. > > > > -fexternal-interpreter currently implements all of TH, quasi-quoting, > > annotations, and all the GHCi features except for some features of the > > debugger. It is also now implemented on Windows, thanks to Tamar > Christina. > > > > *Proposal* > > > > I'd like to propose that going forward we commit to maintaining full > > support for -fexternal-interpreter, with a view to making it the default. > > > > Why? > > > > - -fexternal-interpreter will be a prerequisite for GHCJS support, so > > maintaining full support for TH in -fexternal-interpreter will ensure > that > > everything that works with GHC works with GHCJS. > > - We will be able to make simplifications in GHC and the build system > > once -fexternal-interpreter is the default, because when compiling > with > > -prof or -dynamic we won't have to compile things twice any more. > > - Ultimately we don't want to have two ways of doing everything, > because > > that's harder to maintain. > > > > How? > > > > - I'll make all the TH and quasi-quoting tests run with and without > > -fexternal-interpreter, so it will break validate if one of these > fails. > > > > *Why now?* > > > > There are some TH changes in the pipeline that will need special > attention > > to work with -fexternal-interpreter. e.g. > > https://phabricator.haskell.org/D2286 and > > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so > I'd > > like to raise it now so we can keep the issue in mind. > > > > > > Cheers > > > > Simon > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Wed Jun 22 15:02:10 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 22 Jun 2016 16:02:10 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> Message-ID: One other thing: On 22 June 2016 at 14:36, Richard Eisenberg wrote: > It seems there are nice advantages to this approach, and so I'm fine > requiring support from TH. But here is a comment I just posted on D2286 > requesting more comments in the code: > > --- > I've just spent some time staring at GHCi/TH.hs and friends, and it's > starting to make sense. Would it be possible to add some comments/Notes > there? It would be great to know what is run on the client (GHC, right?) > and what on the server (TH, right?). Also, why do we need a RemoteRef of > an IORef? This, at first, strikes me as odd. I'm sure it makes great > sense once I understand all the other moving parts, but it would be helpful > to have a primer. I also find it a bit confusing that the Message type > contains both messages to the server and messages from the server. For > example, I would expect StartTH and Reify to live in different datatypes, > because the two should never mix. Or am I horribly mistaken? > --- > > Before we require -fexternal-interpreter (which seems to be the endgoal > here), has anyone looked at performance implications? All the marshaling > and unmarshaling has to take a toll. > Yes, I've looked at performance and done a fair bit of optimisation of the current implementation, but mainly for GHCi, not so much for TH yet. For GHCi I think it was <10% of compile time, mainly in shipping the byte code over the pipe. I'll need to do some measurements of TH performance before making it the default. We can probably claw back quite a lot of perf by switching from binary to something else (binary-cbor or store). Cheers Simon > > Richard > > On Jun 22, 2016, at 8:27 AM, Simon Peyton Jones via ghc-devs < > ghc-devs at haskell.org> wrote: > > It’s a great start, thanks > > Simon > > *From:* Simon Marlow [mailto:marlowsd at gmail.com] > *Sent:* 22 June 2016 12:32 > *To:* Simon Peyton Jones > *Cc:* ghc-devs at haskell.org > *Subject:* Re: Require -fexternal-interpreter support for future TH > changes? > > > How's this? > https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/ExternalInterpreter > > I don't want to go into too much detail in the wiki, because details are > more likely to stay current if they're in Notes in the code. There are > already a few Notes (e.g. > https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/ghci/GHCi.hs;619958832cbe11096cae3dac9a0a7a5591163a00$86) > but if anything is confusing I'll happily add more Notes. > > Cheers > > Simon > > > > On 22 June 2016 at 11:50, Simon Marlow wrote: > > On 22 June 2016 at 11:37, Simon Peyton Jones > wrote: > > I’m ok with this. *It would certainly be great not to support TWO > mechanisms indefinitely*. > > What are the disadvantages to committing to this path? Would anyone even > notice? > > > Yes, people who are making changes to TH will need to ensure that their > changes work with -fexternal-interpreter. In some cases that might mean > extra work, e.g. if we do TemplateHaskell/Introspective > then > potentially the whole of HsSyn needs to be binary serializable. That > worries me quite a lot - THSyn is big but tractable, Generic deriving > handled the generation of the binary instances easily enough, but HsSyn is > another matter entirely. > > > There are a lot of moving parts to the implementation, and I for one am > utterly ignorant of how it all works. I would love to see an > implementation overview, either somewhere in the code or on a wiki page. > Things like: > > · How, when, and where in the compiler is the separate process > started? > > · How do the compiler and server communicate? Unix pipes? Is it > the same on Windows and Unix? > > · What is serialised, when, and how? For example, GHC has some > TH code to run. Do we send a syntax tree? Or compile to bytecode and send > that? Or what? > > · How are external references managed. E.g. if the code to be > run refers to ‘map’ I’m sure we don’t serialise the code for ‘map’. > I’m sure there is a lot more. E.g the [wiki:RemoteGHCi wiki page] refers > to “a library implementing a message type…” but I don’t know what that > library is called or where it lives. > > > > Yes, we should really have a page in the commentary with an overview of > the pieces and the main implementation strategy. I'll write one. > Cheers > Simon > > > > Thanks > > Simon > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of *Simon > Marlow > *Sent:* 22 June 2016 09:51 > *To:* ghc-devs at haskell.org > *Subject:* Require -fexternal-interpreter support for future TH changes? > > > *Background* > > A few months ago I added -fexternal-interpreter to GHC: > > - docs: > http://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#ghc-flag--fexternal-interpreter > > - wiki, rationale: https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi > > When -fexternal-interpreter is used, GHC runs interpreted code in a > separate subprocess, and communicates with it using binary messages over a > pipe. > > -fexternal-interpreter currently implements all of TH, quasi-quoting, > annotations, and all the GHCi features except for some features of the > debugger. It is also now implemented on Windows, thanks to Tamar Christina. > > *Proposal* > > I'd like to propose that going forward we commit to maintaining full > support for -fexternal-interpreter, with a view to making it the default. > Why? > > - -fexternal-interpreter will be a prerequisite for GHCJS support, so > maintaining full support for TH in -fexternal-interpreter will ensure that > everything that works with GHC works with GHCJS. > - We will be able to make simplifications in GHC and the build system > once -fexternal-interpreter is the default, because when compiling with > -prof or -dynamic we won't have to compile things twice any more. > - Ultimately we don't want to have two ways of doing everything, > because that's harder to maintain. > > How? > > - I'll make all the TH and quasi-quoting tests run with and without > -fexternal-interpreter, so it will break validate if one of these fails. > > *Why now?* > > There are some TH changes in the pipeline that will need special attention > to work with -fexternal-interpreter. e.g. > https://phabricator.haskell.org/D2286 and > https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Introspective, so > I'd like to raise it now so we can keep the issue in mind. > > > > Cheers > > Simon > > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Wed Jun 22 15:39:21 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Wed, 22 Jun 2016 11:39:21 -0400 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> Message-ID: On Jun 22, 2016, at 10:38 AM, Simon Marlow wrote: > Thanks for the feedback Richard. It's helpful to know which parts of the implementation you found non-obvious. I will write some more Notes, but first: I think what would help most is a place that describes the little state machine that's going on here: the startTH / runTH / finishTH cycle, with possible callbacks in between. All RPC calls are blocking, yes? That certainly simplifies the matter. In the state machine, I think it would help to see clearly what causes the state transition (e.g. splice encountered during renaming, reify call made during splicing) and where the code is located (both source file/function and client vs server). There's just a bunch of moving parts here spread across a number of files and two processes. > > * On why we need a RemoteRef of an IORef - because the IORef lives on the server, so GHC has a RemoteRef to it. Did you see Note [External GHCi pointers] in compiler/ghci/GHCi.hs? Does that help? Somewhat. So the server is sending a pointer (the IORef) to the client? Presumably this pointer is only usable on the server, so the client just ends up sending it back at some point. From the client's point of view, it's just getting an opaque key that only the server can decode. Perhaps this would all become clearer with the overall map. > Should I xref it from somewhere else? Perhaps from libraries/ghci/GHCi/RemoteTypes.hs, on the declaration of RemoteRef. Thanks! Richard From david.feuer at gmail.com Wed Jun 22 16:58:17 2016 From: david.feuer at gmail.com (David Feuer) Date: Wed, 22 Jun 2016 12:58:17 -0400 Subject: How bad would it be for containers to depend on transformers? Message-ID: Currently, containers does not depend on transformers, so it has to duplicate its functionality or just do without. Since transformers is also a GHC boot package, I believe it should be feasible to make containers depend on it. To what extent would that reduce parallelizability of GHC builds or otherwise make people mad? David -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Wed Jun 22 18:24:36 2016 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 22 Jun 2016 14:24:36 -0400 Subject: How bad would it be for containers to depend on transformers? In-Reply-To: References: Message-ID: <20255157-DABF-4450-A71D-398ABE61AB5F@gmail.com> If we're just talking about building one or two transformers then I'd say we should avoid incurring the dependency. The outcry would far far outweigh the code sharing advantage for one or two types. E.g. base duplicates State internally for mapAccumL for instance for this sort of reason. Sent from my iPad > On Jun 22, 2016, at 12:58 PM, David Feuer wrote: > > Currently, containers does not depend on transformers, so it has to duplicate its functionality or just do without. Since transformers is also a GHC boot package, I believe it should be feasible to make containers depend on it. To what extent would that reduce > parallelizability of GHC builds or otherwise make people mad? > > David > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries From simonpj at microsoft.com Wed Jun 22 21:24:05 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 22 Jun 2016 21:24:05 +0000 Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 (15641b0) In-Reply-To: <20160622210820.C04623A300@ghc.haskell.org> References: <20160622210820.C04623A300@ghc.haskell.org> Message-ID: Does anyone know what made T7257 better? Simon | -----Original Message----- | From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of | git at git.haskell.org | Sent: 22 June 2016 22:08 | To: ghc-commits at haskell.org | Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 | (15641b0) | | Repository : ssh://git at git.haskell.org/ghc | | On branch : master | Link : | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fghc.hask | ell.org%2ftrac%2fghc%2fchangeset%2f15641b07f1d3ccb5f35b4f31539ecceb5fb38 | c17%2fghc&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c32fafc88b758 | 43148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=eLrMob | XyWHA691jI3t4pf0CbGybfrVqptmkpTDdtDI8%3d | | >--------------------------------------------------------------- | | commit 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 | Author: Simon Marlow | Date: Wed Jun 22 20:54:59 2016 +0100 | | Accept new (lower) allocations for T7257 | | | >--------------------------------------------------------------- | | 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 | testsuite/tests/perf/should_run/all.T | 3 ++- | 1 file changed, 2 insertions(+), 1 deletion(-) | | diff --git a/testsuite/tests/perf/should_run/all.T | b/testsuite/tests/perf/should_run/all.T | index caf4eff..3cb6f8e 100644 | --- a/testsuite/tests/perf/should_run/all.T | +++ b/testsuite/tests/perf/should_run/all.T | @@ -276,9 +276,10 @@ test('T7257', | [(wordsize(32), 989850664, 10), | # expected value: 1246287228 (i386/Linux) | # 2016-04-06: 989850664 (i386/Linux) no idea | what happened | - (wordsize(64), 1654893248, 5)]), | + (wordsize(64), 1414893248, 5)]), | # 2012-09-21: 1774893760 (amd64/Linux) | # 2015-11-03: 1654893248 (amd64/Linux) | + # 2016-06-22: 1414893248 (amd64/Linux, sizeExpr | fix) | stats_num_field('peak_megabytes_allocated', | [(wordsize(32), 217, 5), | # 2012-10-08: 217 (x86/Linux) | | _______________________________________________ | ghc-commits mailing list | ghc-commits at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.has | kell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | commits&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c32fafc88b75843 | 148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=RftvNpBH | H7bw53EdhgnsdV%2f6M2LNgFVB1t7gCwOTT7A%3d From niteria at gmail.com Wed Jun 22 21:37:22 2016 From: niteria at gmail.com (Bartosz Nitka) Date: Wed, 22 Jun 2016 22:37:22 +0100 Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 (15641b0) In-Reply-To: References: <20160622210820.C04623A300@ghc.haskell.org> Message-ID: Appears to be: a47b62cb3685 Second attempt to fix sizeExpr https://perf.haskell.org/ghc/#revision/9d62d09a6c399c98491b7a63a7a1366c89fcf5db 2016-06-22 22:24 GMT+01:00 Simon Peyton Jones via ghc-devs < ghc-devs at haskell.org>: > Does anyone know what made T7257 better? > > Simon > > | -----Original Message----- > | From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of > | git at git.haskell.org > | Sent: 22 June 2016 22:08 > | To: ghc-commits at haskell.org > | Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 > | (15641b0) > | > | Repository : ssh://git at git.haskell.org/ghc > | > | On branch : master > | Link : > | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fghc.hask > | ell.org%2ftrac%2fghc%2fchangeset%2f15641b07f1d3ccb5f35b4f31539ecceb5fb38 > | c17%2fghc&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c32fafc88b758 > | 43148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=eLrMob > | XyWHA691jI3t4pf0CbGybfrVqptmkpTDdtDI8%3d > | > | >--------------------------------------------------------------- > | > | commit 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 > | Author: Simon Marlow > | Date: Wed Jun 22 20:54:59 2016 +0100 > | > | Accept new (lower) allocations for T7257 > | > | > | >--------------------------------------------------------------- > | > | 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 > | testsuite/tests/perf/should_run/all.T | 3 ++- > | 1 file changed, 2 insertions(+), 1 deletion(-) > | > | diff --git a/testsuite/tests/perf/should_run/all.T > | b/testsuite/tests/perf/should_run/all.T > | index caf4eff..3cb6f8e 100644 > | --- a/testsuite/tests/perf/should_run/all.T > | +++ b/testsuite/tests/perf/should_run/all.T > | @@ -276,9 +276,10 @@ test('T7257', > | [(wordsize(32), 989850664, 10), > | # expected value: 1246287228 (i386/Linux) > | # 2016-04-06: 989850664 (i386/Linux) no idea > | what happened > | - (wordsize(64), 1654893248, 5)]), > | + (wordsize(64), 1414893248, 5)]), > | # 2012-09-21: 1774893760 (amd64/Linux) > | # 2015-11-03: 1654893248 (amd64/Linux) > | + # 2016-06-22: 1414893248 (amd64/Linux, sizeExpr > | fix) > | stats_num_field('peak_megabytes_allocated', > | [(wordsize(32), 217, 5), > | # 2012-10-08: 217 (x86/Linux) > | > | _______________________________________________ > | ghc-commits mailing list > | ghc-commits at haskell.org > | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.has > | kell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- > | commits&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c32fafc88b75843 > | 148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=RftvNpBH > | H7bw53EdhgnsdV%2f6M2LNgFVB1t7gCwOTT7A%3d > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Thu Jun 23 09:24:06 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Thu, 23 Jun 2016 10:24:06 +0100 Subject: Require -fexternal-interpreter support for future TH changes? In-Reply-To: References: <191f618826a545b08f1fbae0e8b2589f@DB4PR30MB030.064d.mgd.msft.net> <5DE4AC08-F9AD-4342-9D86-7ED0A9CC7662@cis.upenn.edu> Message-ID: I've answered all these questions (I hope) in the form of new Notes and signposts, please feel free to comment on this diff: https://phabricator.haskell.org/D2358. I'm happy to add more if needs be. On 22 June 2016 at 16:39, Richard Eisenberg wrote: > > On Jun 22, 2016, at 10:38 AM, Simon Marlow wrote: > > > Thanks for the feedback Richard. It's helpful to know which parts of > the implementation you found non-obvious. I will write some more Notes, > but first: > > I think what would help most is a place that describes the little state > machine that's going on here: the startTH / runTH / finishTH cycle, with > possible callbacks in between. All RPC calls are blocking, yes? That > certainly simplifies the matter. In the state machine, I think it would > help to see clearly what causes the state transition (e.g. splice > encountered during renaming, reify call made during splicing) and where the > code is located (both source file/function and client vs server). There's > just a bunch of moving parts here spread across a number of files and two > processes. > > > > > * On why we need a RemoteRef of an IORef - because the IORef lives on > the server, so GHC has a RemoteRef to it. Did you see Note [External GHCi > pointers] in compiler/ghci/GHCi.hs? Does that help? > > Somewhat. So the server is sending a pointer (the IORef) to the client? > Presumably this pointer is only usable on the server, so the client just > ends up sending it back at some point. From the client's point of view, > it's just getting an opaque key that only the server can decode. Perhaps > this would all become clearer with the overall map. > > > Should I xref it from somewhere else? > > Perhaps from libraries/ghci/GHCi/RemoteTypes.hs, on the declaration of > RemoteRef. > > Thanks! > Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 23 12:59:46 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 23 Jun 2016 12:59:46 +0000 Subject: isInvisible Message-ID: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> Richard I have just spent an hour plumbing the torrid swamp of binder visibility. There is bad naming confusion. We have · Visible · Specified · Invisible The function isVisible returns True for Visible and False otherwise. But isInvisible returns True for Invisible and Specified. And partitionInvisibles, filterOutInvisibleTyVars, filterOutInvisibleTypes etc all treat Invisible and Specified the same. That is, it’s really filterOutInvisibleOrSpecifiedTypes which is terribly clumsy. Sometimes we need to pick up just the Inivisble args, and we don’t have a predicate for that (since isInvisible is taken), so you’ll see in Inst.top_instantiate we are reduced to saying (binderVisibility bndr == Invisible). It’s all very smelly. The trouble is that · In displayed types like (T a b), we display args that are Visible, but not Specified or Invisible · In visible type application like (f @t1 @t2) we can specify type args that are Visible or Specified but not Invisible. Urgh. The trouble is that “invisible” is not the negation of “visible”, which leads to all kinds of confusion. I wonder about changing to · Explicit · Specified · Implicit Then for display we display Explicit args only; for VTA we can specify Explicit or Specified args. So “not Explicit” doesn’t sound structurally like “Implicit” in the way that “not Visible” does sound like “Invisible”. Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Thu Jun 23 13:08:11 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Thu, 23 Jun 2016 09:08:11 -0400 Subject: isInvisible In-Reply-To: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> References: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <17703F45-9BB4-42AB-B9B9-3623B1E17DC0@cis.upenn.edu> On Jun 23, 2016, at 8:59 AM, Simon Peyton Jones wrote: > Richard > > I have just spent an hour plumbing the torrid swamp of binder visibility. There is bad naming confusion. > > We have > > · Visible > > · Specified > > · Invisible > > The function isVisible returns True for Visible and False otherwise. But isInvisible returns True for Invisible and Specified. And partitionInvisibles, filterOutInvisibleTyVars, filterOutInvisibleTypes etc all treat Invisible and Specified the same. That is, it’s really filterOutInvisibleOrSpecifiedTypes which is terribly clumsy. > Here is another design I considered: > data VisibilityFlag > = Visible > | Invisible SpecifiedFlag > > data SpecifiedFlag = Specified | Inferred That might make this all a bit clearer. I avoided this extra layer of indirection, though, as overly ornate. Perhaps I was wrong. isVisible and isInvisible (the functions) are indeed opposites of each other. That's good, in my book. But it is confusing that Specified is lumped in with Invisible here. > > > Sometimes we need to pick up just the Inivisble args, and we don’t have a predicate for that (since isInvisible is taken), so you’ll see in Inst.top_instantiate we are reduced to saying (binderVisibility bndr == Invisible). > > It’s all very smelly. The trouble is that > > · In displayed types like (T a b), we display args that are Visible, but not Specified or Invisible > True. > · In visible type application like (f @t1 @t2) we can specify type args that are Visible or Specified but not Invisible. > No. We can't use visible type application with Visible arguments. If they're Visible, then you don't need the @. > > > Urgh. The trouble is that “invisible” is not the negation of “visible”, which leads to all kinds of confusion. > > I wonder about changing to > > · Explicit > > · Specified > > · Implicit > > Then for display we display Explicit args only; for VTA we can specify Explicit or Specified args. > > So “not Explicit” doesn’t sound structurally like “Implicit” in the way that “not Visible” does sound like “Invisible”. > I don't see the improvement here. "Invisible" and "visible" are antonyms, just like "implicit" and "explicit". Yes, it's true that "implicit" isn't just a prefix put on "explicit", but I hardly think that matters. How about * Required * Specified * Inferred A Required argument is just that: it must be provided at all call sites. A Specified argument is one whose order we know about and can be given by visible type application. An Inferred argument is invented by GHC and cannot be affected by the user. With this phrasing, no word is an antonym of another. Richard > Simon > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 23 13:14:05 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 23 Jun 2016 13:14:05 +0000 Subject: isInvisible In-Reply-To: <17703F45-9BB4-42AB-B9B9-3623B1E17DC0@cis.upenn.edu> References: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> <17703F45-9BB4-42AB-B9B9-3623B1E17DC0@cis.upenn.edu> Message-ID: No. We can't use visible type application with Visible arguments. If they're Visible, then you don't need the @. Ah yes. How about * Required * Specified * Inferred A Required argument is just that: it must be provided at all call sites. A Specified argument is one whose order we know about and can be given by visible type application. An Inferred argument is invented by GHC and cannot be affected by the user. With this phrasing, no word is an antonym of another. I like that. Much more self-explanatory. Shall we go for it? Simon From: Richard Eisenberg [mailto:eir at cis.upenn.edu] Sent: 23 June 2016 14:08 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: Re: isInvisible On Jun 23, 2016, at 8:59 AM, Simon Peyton Jones > wrote: Richard I have just spent an hour plumbing the torrid swamp of binder visibility. There is bad naming confusion. We have • Visible • Specified • Invisible The function isVisible returns True for Visible and False otherwise. But isInvisible returns True for Invisible and Specified. And partitionInvisibles, filterOutInvisibleTyVars, filterOutInvisibleTypes etc all treat Invisible and Specified the same. That is, it’s really filterOutInvisibleOrSpecifiedTypes which is terribly clumsy. Here is another design I considered: > data VisibilityFlag > = Visible > | Invisible SpecifiedFlag > > data SpecifiedFlag = Specified | Inferred That might make this all a bit clearer. I avoided this extra layer of indirection, though, as overly ornate. Perhaps I was wrong. isVisible and isInvisible (the functions) are indeed opposites of each other. That's good, in my book. But it is confusing that Specified is lumped in with Invisible here. Sometimes we need to pick up just the Inivisble args, and we don’t have a predicate for that (since isInvisible is taken), so you’ll see in Inst.top_instantiate we are reduced to saying (binderVisibility bndr == Invisible). It’s all very smelly. The trouble is that • In displayed types like (T a b), we display args that are Visible, but not Specified or Invisible True. • In visible type application like (f @t1 @t2) we can specify type args that are Visible or Specified but not Invisible. No. We can't use visible type application with Visible arguments. If they're Visible, then you don't need the @. Urgh. The trouble is that “invisible” is not the negation of “visible”, which leads to all kinds of confusion. I wonder about changing to • Explicit • Specified • Implicit Then for display we display Explicit args only; for VTA we can specify Explicit or Specified args. So “not Explicit” doesn’t sound structurally like “Implicit” in the way that “not Visible” does sound like “Invisible”. I don't see the improvement here. "Invisible" and "visible" are antonyms, just like "implicit" and "explicit". Yes, it's true that "implicit" isn't just a prefix put on "explicit", but I hardly think that matters. How about * Required * Specified * Inferred A Required argument is just that: it must be provided at all call sites. A Specified argument is one whose order we know about and can be given by visible type application. An Inferred argument is invented by GHC and cannot be affected by the user. With this phrasing, no word is an antonym of another. Richard Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Thu Jun 23 13:16:57 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Thu, 23 Jun 2016 09:16:57 -0400 Subject: isInvisible In-Reply-To: References: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> <17703F45-9BB4-42AB-B9B9-3623B1E17DC0@cis.upenn.edu> Message-ID: > * Required > * Specified > * Inferred > > I like that. Much more self-explanatory. Shall we go for it? > Sure. Now, who gets to do the work? :) Are you in the middle of a refactor around this? If not, I can do this this afternoon. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 23 13:32:39 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 23 Jun 2016 13:32:39 +0000 Subject: isInvisible In-Reply-To: References: <2001ee5a588649f086bed2c692a71862@DB4PR30MB030.064d.mgd.msft.net> <17703F45-9BB4-42AB-B9B9-3623B1E17DC0@cis.upenn.edu> Message-ID: <3e9ec4018c894af8b6126ea7f955c0ab@DB4PR30MB030.064d.mgd.msft.net> It’d be great if you could. I’m about to commit a patch, but it doesn’t affect this much. (It’s just that getting the patch right made me fall into the swamp) S From: Richard Eisenberg [mailto:eir at cis.upenn.edu] Sent: 23 June 2016 14:17 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: Re: isInvisible * Required * Specified * Inferred I like that. Much more self-explanatory. Shall we go for it? Sure. Now, who gets to do the work? :) Are you in the middle of a refactor around this? If not, I can do this this afternoon. Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Thu Jun 23 15:09:39 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Thu, 23 Jun 2016 15:09:39 +0000 Subject: Does anyone know any easy-to-run compile-time benchmark suites? Message-ID: Hi all, I was wondering if anyone has or knows easy-to-run compile-time benchmarks? I'm looking for something like nofib -- ideally after a fresh build I should be able to just run `make` and get some numbers (mainly allocations) back. From mail at joachim-breitner.de Thu Jun 23 15:33:15 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 23 Jun 2016 16:33:15 +0100 Subject: Does anyone know any easy-to-run compile-time benchmark suites? In-Reply-To: References: Message-ID: <1466695995.16347.1.camel@joachim-breitner.de> Hi, Am Donnerstag, den 23.06.2016, 15:09 +0000 schrieb Ömer Sinan Ağacan: > I was wondering if anyone has or knows easy-to-run compile-time > benchmarks? I'm > looking for something like nofib -- ideally after a fresh build I should be > able to just run `make` and get some numbers (mainly allocations) back. nofib reports compile times and (I believe also) compile allocations. If that is not what you are looking for, what is missing? Greetings, Joachim -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From ben at smart-cactus.org Thu Jun 23 16:20:10 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 23 Jun 2016 18:20:10 +0200 Subject: Does anyone know any easy-to-run compile-time benchmark suites? In-Reply-To: <1466695995.16347.1.camel@joachim-breitner.de> References: <1466695995.16347.1.camel@joachim-breitner.de> Message-ID: <878txvnah1.fsf@smart-cactus.org> Joachim Breitner writes: > [ Unknown signature status ] > Hi, > > Am Donnerstag, den 23.06.2016, 15:09 +0000 schrieb Ömer Sinan Ağacan: >> I was wondering if anyone has or knows easy-to-run compile-time >> benchmarks? I'm >> looking for something like nofib -- ideally after a fresh build I should be >> able to just run `make` and get some numbers (mainly allocations) back. > > nofib reports compile times and (I believe also) compile allocations. > If that is not what you are looking for, what is missing? > Indeed, compile allocations are reported on a per-module basis. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From simonpj at microsoft.com Fri Jun 24 07:58:10 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 24 Jun 2016 07:58:10 +0000 Subject: Testsuite cleaning Message-ID: Thomas During debugging I often compile a single test program ghc -c T1969.hs But the new testsuite setup doesn’t remove .hi and .o files before running a test, so make TEST=T1969 says bytes allocated value is too low: … Deviation T1969(normal) bytes allocated: -95.2 % Reason? Compilation was not required! Non-perf tests fail in the same way +compilation IS NOT required *** unexpected failure for T11480b(normal) I’m sure this didn’t use to happen. It’s not fatal, because can manually remove those .o files, but it’s a bit of a nuisance. Might it be easy to restore the old behaviour? Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Fri Jun 24 08:26:55 2016 From: omeragacan at gmail.com (=?UTF-8?Q?=C3=96mer_Sinan_A=C4=9Facan?=) Date: Fri, 24 Jun 2016 08:26:55 +0000 Subject: Testsuite cleaning In-Reply-To: References: Message-ID: I also realized this after a rebase I did yesterday. Should be a recent thing. 2016-06-24 7:58 GMT+00:00 Simon Peyton Jones via ghc-devs : > Thomas > > During debugging I often compile a single test program > > ghc -c T1969.hs > > But the new testsuite setup doesn’t remove .hi and .o files before running a > test, so > > make TEST=T1969 > > says > > bytes allocated value is too low: > > … > > Deviation T1969(normal) bytes allocated: -95.2 % > > Reason? Compilation was not required! > > Non-perf tests fail in the same way > > +compilation IS NOT required > > *** unexpected failure for T11480b(normal) > > I’m sure this didn’t use to happen. > > It’s not fatal, because can manually remove those .o files, but it’s a bit > of a nuisance. Might it be easy to restore the old behaviour? > > Thanks > > Simon > > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > From thomasmiedema at gmail.com Fri Jun 24 09:05:09 2016 From: thomasmiedema at gmail.com (Thomas Miedema) Date: Fri, 24 Jun 2016 11:05:09 +0200 Subject: Testsuite cleaning In-Reply-To: References: Message-ID: Fixed. See https://ghc.haskell.org/trac/ghc/ticket/12112 for details. On Fri, Jun 24, 2016 at 10:26 AM, Ömer Sinan Ağacan wrote: > I also realized this after a rebase I did yesterday. Should be a recent > thing. > > 2016-06-24 7:58 GMT+00:00 Simon Peyton Jones via ghc-devs > : > > Thomas > > > > During debugging I often compile a single test program > > > > ghc -c T1969.hs > > > > But the new testsuite setup doesn’t remove .hi and .o files before > running a > > test, so > > > > make TEST=T1969 > > > > says > > > > bytes allocated value is too low: > > > > … > > > > Deviation T1969(normal) bytes allocated: -95.2 % > > > > Reason? Compilation was not required! > > > > Non-perf tests fail in the same way > > > > +compilation IS NOT required > > > > *** unexpected failure for T11480b(normal) > > > > I’m sure this didn’t use to happen. > > > > It’s not fatal, because can manually remove those .o files, but it’s a > bit > > of a nuisance. Might it be easy to restore the old behaviour? > > > > Thanks > > > > Simon > > > > > > > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Jun 24 10:00:19 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 24 Jun 2016 10:00:19 +0000 Subject: Testsuite cleaning In-Reply-To: References: Message-ID: Thanks Thomas! From: Thomas Miedema [mailto:thomasmiedema at gmail.com] Sent: 24 June 2016 10:05 To: Ömer Sinan Ağacan Cc: Simon Peyton Jones ; ghc-devs at haskell.org Subject: Re: Testsuite cleaning Fixed. See https://ghc.haskell.org/trac/ghc/ticket/12112 for details. On Fri, Jun 24, 2016 at 10:26 AM, Ömer Sinan Ağacan > wrote: I also realized this after a rebase I did yesterday. Should be a recent thing. 2016-06-24 7:58 GMT+00:00 Simon Peyton Jones via ghc-devs >: > Thomas > > During debugging I often compile a single test program > > ghc -c T1969.hs > > But the new testsuite setup doesn’t remove .hi and .o files before running a > test, so > > make TEST=T1969 > > says > > bytes allocated value is too low: > > … > > Deviation T1969(normal) bytes allocated: -95.2 % > > Reason? Compilation was not required! > > Non-perf tests fail in the same way > > +compilation IS NOT required > > *** unexpected failure for T11480b(normal) > > I’m sure this didn’t use to happen. > > It’s not fatal, because can manually remove those .o files, but it’s a bit > of a nuisance. Might it be easy to restore the old behaviour? > > Thanks > > Simon > > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Jun 24 11:20:15 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 24 Jun 2016 11:20:15 +0000 Subject: Help on first ticket In-Reply-To: <87vb1ok354.fsf@smart-cactus.org> References: <87vb1ok354.fsf@smart-cactus.org> Message-ID: Richard, did you get on ok? Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ben | Gamari | Sent: 04 June 2016 23:20 | To: Richard Fung ; ghc-devs at haskell.org | Subject: Re: Help on first ticket | | Richard Fung writes: | | > Hello! I apologize if this isn't the right place to ask; if it isn't | > please steer me in the right direction. | > | Hi Richard! | | > Would anyone be willing to advise me on my first ticket? I've been | > trying to work on it on and off but haven't made much progress on my | own. | > | > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 | > | Great, I'm happy to hear that someone has picked this one up. I think | it is a nice choice for a self-contained newcomers project. | | > I think I understand the issue conceptually but I don't know where | to | > look for the code that needs to be changed.. | > | I don't know where the code responsible for this is off the top of my | head, however I can provide some pointers. | | So the unfoldings you are looking to preserve come from interface | files. | The machinery for all of this is in compiler/iface. IfaceSyn.hs is of | particular interest and there you will find the definition of | IfaceUnfolding, which is the unfolding representation which is stored | in the interface file. Unfoldings live inside of IdInfo values, which | hold various miscellaneous information which we need to preserve about | a particular Id (identifier). | | There is a somewhat useful comment regarding how IdInfo is treated | above the definition of IfaceIdInfo in IfaceSyn. In particular it | seems that interface files for modules compiled with -O0 will have | their IdInfo fields set to NoInfo. It's not clear what happens when an | interface file is read. However, grepping for NoInfo reveals a use- | site in TcIface.tcIdInfo which looks interesting (in particular the | ignore_prags guard). I think this should be enough to get you going on | the interface file part of this. | | The other part of this ticket is deciding whether to use an unfolding | when considering whether to inline. This will be done in the | simplifier (compiler/simplCore). Grepping for "inline" and "unfold" in | simplCore/Simplify.hs (as well as reading the notes in that file) will | likely be enough to get you started. | | Do let me know if you still feel lost or want to discuss this further. | I look forward to hearing how it goes. | | Cheers, | | - Ben | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c5ce47a744a1448f | ff5cb08d38cc666b8%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=V22RG%2 | fAiO1lD5bLCR%2fXz2jv5QCzYAK5HUi6dDaAFQLA%3d From simonpj at microsoft.com Fri Jun 24 14:12:11 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 24 Jun 2016 14:12:11 +0000 Subject: [Diffusion] [Build Failed] rGHCbb84ee44e30e: Improve pretty-printing of Avail In-Reply-To: <20160624135011.22098.19863.00515FBC@phabricator.haskell.org> References: <20160624135011.22098.19863.00515FBC@phabricator.haskell.org> Message-ID: <6e3375b95b624d86bc97029723a0865b@AM3PR30MB019.064d.mgd.msft.net> These failures are odd. One is this change in T8761 which I'm sure is not my fault. I saw that simonmar did some hFlush thing -- could that be it? Simon +++ ./T8761.run/T8761.comp.stderr.normalised 2016-06-24 15:00:22.975083533 +0100 @@ -1,3 +1,7 @@ +pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) +pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) +pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where + Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) T8761.hs:(16,1)-(39,13): Splicing declarations do { [qx1, qy1, qz1] <- mapM (/ i -> newName $ "x" ++ show i) [1, 2, 3]; @@ -119,10 +123,6 @@ pattern Pup x <- MkUnivProv x pattern Puep :: forall a. forall b. Show b => a -> b -> (ExProv, a) pattern Puep x y <- (MkExProv y, x) -pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) -pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) -pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where - Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) pattern T8761.P :: GHC.Types.Bool pattern T8761.Pe :: () => forall (a0_0 :: *) . a0_0 -> T8761.Ex pattern T8761.Pu :: forall (a0_0 :: *) . a0_0 -> a0_0 | -----Original Message----- | From: noreply at phabricator.haskell.org | [mailto:noreply at phabricator.haskell.org] | Sent: 24 June 2016 14:50 | To: Simon Peyton Jones | Subject: [Diffusion] [Build Failed] rGHCbb84ee44e30e: Improve pretty- | printing of Avail | | Harbormaster failed to build B10226: rGHCbb84ee44e30e: Improve pretty- | printing of Avail! | | BRANCHES | master, wip/rae | | USERS | simonpj (Author) | | COMMIT | https://phabricator.haskell.org/rGHCbb84ee44e30e | | EMAIL PREFERENCES | https://phabricator.haskell.org/settings/panel/emailpreferences/ | | To: simonpj, Harbormaster From minesasecret at gmail.com Fri Jun 24 18:05:03 2016 From: minesasecret at gmail.com (Richard Fung) Date: Fri, 24 Jun 2016 11:05:03 -0700 Subject: Help on first ticket In-Reply-To: References: <87vb1ok354.fsf@smart-cactus.org> Message-ID: Hi Simon, I am making progress but slowly (I only have time to work on this outside of work unfortunately). If this needs to be done soon feel free to reassign it to someone else! Otherwise, while at times I feel like I'm over my head I would like to keep at it. On Fri, Jun 24, 2016 at 4:20 AM, Simon Peyton Jones wrote: > Richard, did you get on ok? > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ben > | Gamari > | Sent: 04 June 2016 23:20 > | To: Richard Fung ; ghc-devs at haskell.org > | Subject: Re: Help on first ticket > | > | Richard Fung writes: > | > | > Hello! I apologize if this isn't the right place to ask; if it isn't > | > please steer me in the right direction. > | > > | Hi Richard! > | > | > Would anyone be willing to advise me on my first ticket? I've been > | > trying to work on it on and off but haven't made much progress on my > | own. > | > > | > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 > | > > | Great, I'm happy to hear that someone has picked this one up. I think > | it is a nice choice for a self-contained newcomers project. > | > | > I think I understand the issue conceptually but I don't know where > | to > | > look for the code that needs to be changed.. > | > > | I don't know where the code responsible for this is off the top of my > | head, however I can provide some pointers. > | > | So the unfoldings you are looking to preserve come from interface > | files. > | The machinery for all of this is in compiler/iface. IfaceSyn.hs is of > | particular interest and there you will find the definition of > | IfaceUnfolding, which is the unfolding representation which is stored > | in the interface file. Unfoldings live inside of IdInfo values, which > | hold various miscellaneous information which we need to preserve about > | a particular Id (identifier). > | > | There is a somewhat useful comment regarding how IdInfo is treated > | above the definition of IfaceIdInfo in IfaceSyn. In particular it > | seems that interface files for modules compiled with -O0 will have > | their IdInfo fields set to NoInfo. It's not clear what happens when an > | interface file is read. However, grepping for NoInfo reveals a use- > | site in TcIface.tcIdInfo which looks interesting (in particular the > | ignore_prags guard). I think this should be enough to get you going on > | the interface file part of this. > | > | The other part of this ticket is deciding whether to use an unfolding > | when considering whether to inline. This will be done in the > | simplifier (compiler/simplCore). Grepping for "inline" and "unfold" in > | simplCore/Simplify.hs (as well as reading the notes in that file) will > | likely be enough to get you started. > | > | Do let me know if you still feel lost or want to discuss this further. > | I look forward to hearing how it goes. > | > | Cheers, > | > | - Ben > | _______________________________________________ > | ghc-devs mailing list > | ghc-devs at haskell.org > | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h > | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- > | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c5ce47a744a1448f > | ff5cb08d38cc666b8%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=V22RG%2 > | fAiO1lD5bLCR%2fXz2jv5QCzYAK5HUi6dDaAFQLA%3d > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Jun 24 19:26:30 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 24 Jun 2016 19:26:30 +0000 Subject: Help on first ticket In-Reply-To: References: <87vb1ok354.fsf@smart-cactus.org> Message-ID: <7eb267e6aec944a3b07af79d8eb51033@AM3PR30MB019.064d.mgd.msft.net> Great. No rush. Yell if you need help. Simon From: Richard Fung [mailto:minesasecret at gmail.com] Sent: 24 June 2016 19:05 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: Re: Help on first ticket Hi Simon, I am making progress but slowly (I only have time to work on this outside of work unfortunately). If this needs to be done soon feel free to reassign it to someone else! Otherwise, while at times I feel like I'm over my head I would like to keep at it. On Fri, Jun 24, 2016 at 4:20 AM, Simon Peyton Jones > wrote: Richard, did you get on ok? Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ben | Gamari | Sent: 04 June 2016 23:20 | To: Richard Fung >; ghc-devs at haskell.org | Subject: Re: Help on first ticket | | Richard Fung > writes: | | > Hello! I apologize if this isn't the right place to ask; if it isn't | > please steer me in the right direction. | > | Hi Richard! | | > Would anyone be willing to advise me on my first ticket? I've been | > trying to work on it on and off but haven't made much progress on my | own. | > | > It's ticket #9370: https://ghc.haskell.org/trac/ghc/ticket/9370 | > | Great, I'm happy to hear that someone has picked this one up. I think | it is a nice choice for a self-contained newcomers project. | | > I think I understand the issue conceptually but I don't know where | to | > look for the code that needs to be changed.. | > | I don't know where the code responsible for this is off the top of my | head, however I can provide some pointers. | | So the unfoldings you are looking to preserve come from interface | files. | The machinery for all of this is in compiler/iface. IfaceSyn.hs is of | particular interest and there you will find the definition of | IfaceUnfolding, which is the unfolding representation which is stored | in the interface file. Unfoldings live inside of IdInfo values, which | hold various miscellaneous information which we need to preserve about | a particular Id (identifier). | | There is a somewhat useful comment regarding how IdInfo is treated | above the definition of IfaceIdInfo in IfaceSyn. In particular it | seems that interface files for modules compiled with -O0 will have | their IdInfo fields set to NoInfo. It's not clear what happens when an | interface file is read. However, grepping for NoInfo reveals a use- | site in TcIface.tcIdInfo which looks interesting (in particular the | ignore_prags guard). I think this should be enough to get you going on | the interface file part of this. | | The other part of this ticket is deciding whether to use an unfolding | when considering whether to inline. This will be done in the | simplifier (compiler/simplCore). Grepping for "inline" and "unfold" in | simplCore/Simplify.hs (as well as reading the notes in that file) will | likely be enough to get you started. | | Do let me know if you still feel lost or want to discuss this further. | I look forward to hearing how it goes. | | Cheers, | | - Ben | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c5ce47a744a1448f | ff5cb08d38cc666b8%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=V22RG%2 | fAiO1lD5bLCR%2fXz2jv5QCzYAK5HUi6dDaAFQLA%3d -------------- next part -------------- An HTML attachment was scrubbed... URL: From harendra.kumar at gmail.com Sat Jun 25 21:26:47 2016 From: harendra.kumar at gmail.com (Harendra Kumar) Date: Sun, 26 Jun 2016 02:56:47 +0530 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: <87fus9r30u.fsf@smart-cactus.org> References: <87mvml5yfg.fsf@smart-cactus.org> <87y46548ea.fsf@smart-cactus.org> <87fus9r30u.fsf@smart-cactus.org> Message-ID: On 19 June 2016 at 14:03, Ben Gamari wrote: > > Indeed it would be great if you could provide the program that produced > this code. > > >> It would be great to open Trac tickets to track some of the optimization Ok, I created an account on ghc trac and raised two tickets: #12231 & #12232. Yay! I also added the code branch to reproduce this on github ( https://github.com/harendra-kumar/unicode-transforms/tree/ghc-trac-12231). -harendra -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Sun Jun 26 02:29:37 2016 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 25 Jun 2016 22:29:37 -0400 Subject: T8761 failing for ext-interp Message-ID: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> Hi Simon, Phab tells us that T8761 is failing for the ext-interp way, as of d2006d050e7a9111c0c448d6262f8994ef5761b7 (Run all TH tests with -fexternal-interpreter (#12219)). See https://phabricator.haskell.org/B10229 Thanks, Richard From mle+hs at mega-nerd.com Sun Jun 26 05:23:42 2016 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Sun, 26 Jun 2016 15:23:42 +1000 Subject: T8761 failing for ext-interp In-Reply-To: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> Message-ID: <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> Richard Eisenberg wrote: > Phab tells us that T8761 is failing for the ext-interp way, as of > d2006d050e7a9111c0c448d6262f8994ef5761b7 (Run all TH tests with > -fexternal-interpreter (#12219)). See https://phabricator.haskell.org/B10229 Compling with BuildFlavour == perf-llvm results in 42 test failures, the vast majority being TH related along with a small number of GHCi tests. I'm currently doing a git bisect to find which commit broken this, but I do know its something after 9a34bf1985. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From marlowsd at gmail.com Sun Jun 26 06:04:19 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Sun, 26 Jun 2016 07:04:19 +0100 Subject: T8761 failing for ext-interp In-Reply-To: <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> Message-ID: Erik, could it be the same symptom as Edward is seeing here? https://ghc.haskell.org/trac/ghc/ticket/12230 On 26 June 2016 at 06:23, Erik de Castro Lopo wrote: > Richard Eisenberg wrote: > > > Phab tells us that T8761 is failing for the ext-interp way, as of > > d2006d050e7a9111c0c448d6262f8994ef5761b7 (Run all TH tests with > > -fexternal-interpreter (#12219)). See > https://phabricator.haskell.org/B10229 > > Compling with BuildFlavour == perf-llvm results in 42 test failures, > the vast majority being TH related along with a small number of > GHCi tests. > > I'm currently doing a git bisect to find which commit broken this, > but I do know its something after 9a34bf1985. > > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mle+hs at mega-nerd.com Sun Jun 26 06:22:50 2016 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Sun, 26 Jun 2016 16:22:50 +1000 Subject: T8761 failing for ext-interp In-Reply-To: References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> Message-ID: <20160626162250.314aae01ca716c4a2c2cd217@mega-nerd.com> Simon Marlow wrote: > Erik, could it be the same symptom as Edward is seeing here? > https://ghc.haskell.org/trac/ghc/ticket/12230 Yes it is. Cheers, Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From mle+hs at mega-nerd.com Sun Jun 26 06:29:19 2016 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Sun, 26 Jun 2016 16:29:19 +1000 Subject: T8761 failing for ext-interp In-Reply-To: <20160626162250.314aae01ca716c4a2c2cd217@mega-nerd.com> References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> <20160626162250.314aae01ca716c4a2c2cd217@mega-nerd.com> Message-ID: <20160626162919.32fc6b26a9be63c87efad019@mega-nerd.com> Erik de Castro Lopo wrote: > > Erik, could it be the same symptom as Edward is seeing here? > > https://ghc.haskell.org/trac/ghc/ticket/12230 > > Yes it is. Just to provide a little more info, the tests I'm seeing fail (perf-llvm) are: TEST="TH_repUnboxedTuples T10828 T10596 TH_reifyMkName T9064 T8628 T11797 T10796b TH_reifyDecl2 TH_repPrim2 T10891 ClosedFam1TH ghci006 TH_reifyInstances TH_repPrim T9692 prog001 TH_Roles3 T10796a T8639_api TH_reifyDecl1 T5362 T2222 T5037 T8884 TH_TyInstWhere2 T11341 TH_foreignCallingConventions T3920 T7477 T9738 process009 T8953 T4135 T2700 TH_Roles4 T9262 TH_RichKinds2 TH_repGuard T8761 ghci004 T4188 TH_RichKinds" Some examples of the failue are: T10596.hs:1:1: error: Exception when trying to run compile-time code: ghc-stage2: ghc-iserv terminated (-11) Code: do { putQ (100 :: Int); x <- (getQ :: Q (Maybe Int)); ($) runIO print x; .... } T9064.hs:1:1: error: Exception when trying to run compile-time code: ghc-stage2: ghc-iserv terminated (-11) Code: do { info <- reify ''C; ($) runIO do { ($) putStrLn pprint info; .... }; return [] } TH_RichKinds2.hs:1:1: error: Exception when trying to run compile-time code: ghc-stage2: ghc-iserv terminated (-11) Code: let fixKs :: String -> String fixKs s = ... in do { decls <- [d| data SMaybe :: (k -> *) -> (Maybe k) -> * where SNothing :: SMaybe s Nothing SJust :: s a -> SMaybe s (Just a) type instance Map f (h : t) = (f h) : (Map f t) type instance Map f '[] = '[] |]; reportWarning (fixKs (pprint decls)); .... } So yes, very similar to #12230. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From marlowsd at gmail.com Sun Jun 26 07:14:08 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Sun, 26 Jun 2016 08:14:08 +0100 Subject: T8761 failing for ext-interp In-Reply-To: <20160626162919.32fc6b26a9be63c87efad019@mega-nerd.com> References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> <20160626162250.314aae01ca716c4a2c2cd217@mega-nerd.com> <20160626162919.32fc6b26a9be63c87efad019@mega-nerd.com> Message-ID: Is it just perf-llvm? Does validate fail? What platform is this? On 26 June 2016 at 07:29, Erik de Castro Lopo wrote: > Erik de Castro Lopo wrote: > > > > Erik, could it be the same symptom as Edward is seeing here? > > > https://ghc.haskell.org/trac/ghc/ticket/12230 > > > > Yes it is. > > Just to provide a little more info, the tests I'm seeing fail (perf-llvm) > are: > > TEST="TH_repUnboxedTuples T10828 T10596 TH_reifyMkName T9064 T8628 > T11797 T10796b TH_reifyDecl2 TH_repPrim2 T10891 ClosedFam1TH > ghci006 TH_reifyInstances TH_repPrim T9692 prog001 TH_Roles3 > T10796a T8639_api TH_reifyDecl1 T5362 T2222 T5037 T8884 > TH_TyInstWhere2 > T11341 TH_foreignCallingConventions T3920 T7477 T9738 process009 > T8953 > T4135 T2700 TH_Roles4 T9262 TH_RichKinds2 TH_repGuard T8761 > ghci004 T4188 > TH_RichKinds" > > > Some examples of the failue are: > > T10596.hs:1:1: error: > Exception when trying to run compile-time code: > ghc-stage2: ghc-iserv terminated (-11) > Code: do { putQ (100 :: Int); > x <- (getQ :: Q (Maybe Int)); > ($) runIO print x; > .... } > > > T9064.hs:1:1: error: > Exception when trying to run compile-time code: > ghc-stage2: ghc-iserv terminated (-11) > Code: do { info <- reify ''C; > ($) > runIO > do { ($) putStrLn pprint info; > .... }; > return [] } > > > TH_RichKinds2.hs:1:1: error: > Exception when trying to run compile-time code: > ghc-stage2: ghc-iserv terminated (-11) > Code: let > fixKs :: String -> String > fixKs s = ... > in > do { decls <- [d| data SMaybe :: (k -> *) -> (Maybe k) -> * > where > SNothing :: SMaybe s Nothing > SJust :: s a -> SMaybe s (Just a) > > type instance Map f (h : t) = (f h) : (Map f > t) > type instance Map f '[] = '[] |]; > reportWarning (fixKs (pprint decls)); > .... } > > > So yes, very similar to #12230. > > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mle+hs at mega-nerd.com Sun Jun 26 07:38:49 2016 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Sun, 26 Jun 2016 17:38:49 +1000 Subject: T8761 failing for ext-interp In-Reply-To: References: <530DE4B1-8DC1-4DA3-AE58-E7E18483BBAE@cis.upenn.edu> <20160626152342.9e4e4e522f6402cde2ea3fc2@mega-nerd.com> <20160626162250.314aae01ca716c4a2c2cd217@mega-nerd.com> <20160626162919.32fc6b26a9be63c87efad019@mega-nerd.com> Message-ID: <20160626173849.5beb21b201968adfce08f818@mega-nerd.com> Simon Marlow wrote: > Is it just perf-llvm? It seems to be. I build quite a large number of configurations in my Jenkins instance. All of the configurations other than perf-llvm built fine. > Does validate fail? I actually haven't tried validate directly because my build configrations explicitly set BuildFlavour before building and running 'make test'. > What platform is this? This particular failure is on x86_64/linux. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From ben at smart-cactus.org Sun Jun 26 08:53:09 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Sun, 26 Jun 2016 10:53:09 +0200 Subject: CMM-to-ASM: Register allocation wierdness In-Reply-To: References: <87mvml5yfg.fsf@smart-cactus.org> <87y46548ea.fsf@smart-cactus.org> <87fus9r30u.fsf@smart-cactus.org> Message-ID: <87k2hcl4ay.fsf@smart-cactus.org> Harendra Kumar writes: > On 19 June 2016 at 14:03, Ben Gamari wrote: > >> >> Indeed it would be great if you could provide the program that produced >> this code. >> >> >> It would be great to open Trac tickets to track some of the optimization > > > Ok, I created an account on ghc trac and raised two tickets: #12231 & > #12232. Yay! I also added the code branch to reproduce this on github ( > https://github.com/harendra-kumar/unicode-transforms/tree/ghc-trac-12231). > Great job summarizing the issue. Thanks! Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From chrisdone at gmail.com Sun Jun 26 10:28:55 2016 From: chrisdone at gmail.com (Christopher Done) Date: Sun, 26 Jun 2016 12:28:55 +0200 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: I've been pondering how feasible it would be to: * Compile in stages a module with the byte code linker * Keep hold of the Core source * Interpret the Core AST within Haskell * When encountering built-in/primitives (or things from other libraries), we compile that Core term and link it as an HValue and then run it with the arguments expected. So () would be such a HValue, as would be "show" which in interpretable unoptimized Core would take an extra argument for the Show instance. When passing in values to such "foreign" functions it would wrap them up in an interpretive way. This is the hypothetical idea, it seems like it would yield a really trivial way to write a new and interesting interpreter for GHC Haskell without having to re-implement any prim ops, ready to work on regular Haskell code. In my case, I would use this to write an interpreter which: * is not tagless, so we preserve type info * allows top-level names to be redefined * when a function is applied, it checks the type of its arguments Both of these are pretty much necessary for being able to do in-place update of a running program while developing (a la Emacs or Smalltalk), and type tags let us throw a regular Haskell exception of type error, a la deferred type errors. It means in your running program, if you make a mistake or forget to update one part, it doesn't bring the whole program down with an RTS error or a segfault, maybe a handler in a thread (like a server or a video game) throws an exception and the developer just updates their code and tries again. I'd love support for something like this, but I'd rather not have to re-create the world just to add this capability. Because it's really just conceptually regular interpreted GHC Haskell plus type tags and updating, it seems like it should be a small diff. Any input into this? How far away is GHC's current architecture from supporting such a concept? Ciao! -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Mon Jun 27 02:11:32 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sun, 26 Jun 2016 22:11:32 -0400 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: <1466992830-sup-1776@sabre> I am not sure I entirely understand your proposal, but a good way of finding out if it works is giving it a try. Excerpts from Christopher Done's message of 2016-06-26 06:28:55 -0400: > I've been pondering how feasible it would be to: > > * Compile in stages a module with the byte code linker > * Keep hold of the Core source > * Interpret the Core AST within Haskell > * When encountering built-in/primitives (or things from other libraries), > we compile that Core term and link it as an HValue and then run it with the > arguments expected. So () would be such a HValue, as would be "show" which > in interpretable unoptimized Core would take an extra argument for the Show > instance. When passing in values to such "foreign" functions it would wrap > them up in an interpretive way. I don't understand what the bytecode format has to do here. Since your suggestion is to just store Core you can just compile to object code. I prototyped "fat interface" files https://ghc.haskell.org/trac/ghc/ticket/10871 which store core into interface files, so they could be compiled later. The patchset was here: https://github.com/ezyang/ghc/tree/ghc-fat-interface > This is the hypothetical idea, it seems like it would yield a really > trivial way to write a new and interesting interpreter for GHC Haskell > without having to re-implement any prim ops, ready to work on regular > Haskell code. > > In my case, I would use this to write an interpreter which: > > * is not tagless, so we preserve type info > * allows top-level names to be redefined > * when a function is applied, it checks the type of its arguments > > Both of these are pretty much necessary for being able to do in-place > update of a running program while developing (a la Emacs or Smalltalk), and > type tags let us throw a regular Haskell exception of type error, a la > deferred type errors. It means in your running program, if you make a > mistake or forget to update one part, it doesn't bring the whole program > down with an RTS error or a segfault, maybe a handler in a thread (like a > server or a video game) throws an exception and the developer just updates > their code and tries again. > > I'd love support for something like this, but I'd rather not have to > re-create the world just to add this capability. Because it's really just > conceptually regular interpreted GHC Haskell plus type tags and updating, > it seems like it should be a small diff. > > Any input into this? How far away is GHC's current architecture from > supporting such a concept? Well, if you are going to support update you need to make sure that the tag information is more elaborate than what GHC currently supports (a type would just be a Name, which is going to get reused when you recompile.) Edward From marlowsd at gmail.com Mon Jun 27 07:42:30 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 27 Jun 2016 08:42:30 +0100 Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 (15641b0) In-Reply-To: References: <20160622210820.C04623A300@ghc.haskell.org> Message-ID: Yes, it was the sizeExpr fix. It validated locally and on Travis, but I'm guessing it was right on the boundary. On 22 June 2016 at 22:37, Bartosz Nitka wrote: > Appears to be: > a47b62cb3685 Second attempt to fix sizeExpr > > https://perf.haskell.org/ghc/#revision/9d62d09a6c399c98491b7a63a7a1366c89fcf5db > > 2016-06-22 22:24 GMT+01:00 Simon Peyton Jones via ghc-devs < > ghc-devs at haskell.org>: > >> Does anyone know what made T7257 better? >> >> Simon >> >> | -----Original Message----- >> | From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of >> | git at git.haskell.org >> | Sent: 22 June 2016 22:08 >> | To: ghc-commits at haskell.org >> | Subject: [commit: ghc] master: Accept new (lower) allocations for T7257 >> | (15641b0) >> | >> | Repository : ssh://git at git.haskell.org/ghc >> | >> | On branch : master >> | Link : >> | >> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fghc.hask >> | ell.org >> %2ftrac%2fghc%2fchangeset%2f15641b07f1d3ccb5f35b4f31539ecceb5fb38 >> | c17%2fghc&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com >> %7c32fafc88b758 >> | 43148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=eLrMob >> | XyWHA691jI3t4pf0CbGybfrVqptmkpTDdtDI8%3d >> | >> | >--------------------------------------------------------------- >> | >> | commit 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 >> | Author: Simon Marlow >> | Date: Wed Jun 22 20:54:59 2016 +0100 >> | >> | Accept new (lower) allocations for T7257 >> | >> | >> | >--------------------------------------------------------------- >> | >> | 15641b07f1d3ccb5f35b4f31539ecceb5fb38c17 >> | testsuite/tests/perf/should_run/all.T | 3 ++- >> | 1 file changed, 2 insertions(+), 1 deletion(-) >> | >> | diff --git a/testsuite/tests/perf/should_run/all.T >> | b/testsuite/tests/perf/should_run/all.T >> | index caf4eff..3cb6f8e 100644 >> | --- a/testsuite/tests/perf/should_run/all.T >> | +++ b/testsuite/tests/perf/should_run/all.T >> | @@ -276,9 +276,10 @@ test('T7257', >> | [(wordsize(32), 989850664, 10), >> | # expected value: 1246287228 (i386/Linux) >> | # 2016-04-06: 989850664 (i386/Linux) no idea >> | what happened >> | - (wordsize(64), 1654893248, 5)]), >> | + (wordsize(64), 1414893248, 5)]), >> | # 2012-09-21: 1774893760 (amd64/Linux) >> | # 2015-11-03: 1654893248 (amd64/Linux) >> | + # 2016-06-22: 1414893248 (amd64/Linux, sizeExpr >> | fix) >> | stats_num_field('peak_megabytes_allocated', >> | [(wordsize(32), 217, 5), >> | # 2012-10-08: 217 (x86/Linux) >> | >> | _______________________________________________ >> | ghc-commits mailing list >> | ghc-commits at haskell.org >> | >> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.has >> | kell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- >> | commits&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com >> %7c32fafc88b75843 >> | 148b2a08d39ae1ea3f%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=RftvNpBH >> | H7bw53EdhgnsdV%2f6M2LNgFVB1t7gCwOTT7A%3d >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Mon Jun 27 07:48:10 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 27 Jun 2016 08:48:10 +0100 Subject: [Diffusion] [Build Failed] rGHCbb84ee44e30e: Improve pretty-printing of Avail In-Reply-To: <6e3375b95b624d86bc97029723a0865b@AM3PR30MB019.064d.mgd.msft.net> References: <20160624135011.22098.19863.00515FBC@phabricator.haskell.org> <6e3375b95b624d86bc97029723a0865b@AM3PR30MB019.064d.mgd.msft.net> Message-ID: I believe I've just fixed this. I think it was non-deterministic in some way that I don't fully understand, but hopefully I've made it deterministic now. https://phabricator.haskell.org/rGHC7843c71c7e48cdba115bef422184e855ede23a67 On 24 June 2016 at 15:12, Simon Peyton Jones via ghc-devs < ghc-devs at haskell.org> wrote: > These failures are odd. One is this change in T8761 which I'm sure is not > my fault. I saw that simonmar did some hFlush thing -- could that be it? > > Simon > > > +++ ./T8761.run/T8761.comp.stderr.normalised 2016-06-24 > 15:00:22.975083533 +0100 > @@ -1,3 +1,7 @@ > +pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) > +pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) > +pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where > + Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) > T8761.hs:(16,1)-(39,13): Splicing declarations > do { [qx1, qy1, qz1] <- mapM > (/ i -> newName $ "x" ++ show i) [1, 2, 3]; > @@ -119,10 +123,6 @@ > pattern Pup x <- MkUnivProv x > pattern Puep :: forall a. forall b. Show b => a -> b -> (ExProv, a) > pattern Puep x y <- (MkExProv y, x) > -pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) > -pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) > -pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where > - Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) > pattern T8761.P :: GHC.Types.Bool > pattern T8761.Pe :: () => forall (a0_0 :: *) . a0_0 -> T8761.Ex > pattern T8761.Pu :: forall (a0_0 :: *) . a0_0 -> a0_0 > > | -----Original Message----- > | From: noreply at phabricator.haskell.org > | [mailto:noreply at phabricator.haskell.org] > | Sent: 24 June 2016 14:50 > | To: Simon Peyton Jones > | Subject: [Diffusion] [Build Failed] rGHCbb84ee44e30e: Improve pretty- > | printing of Avail > | > | Harbormaster failed to build B10226: rGHCbb84ee44e30e: Improve pretty- > | printing of Avail! > | > | BRANCHES > | master, wip/rae > | > | USERS > | simonpj (Author) > | > | COMMIT > | https://phabricator.haskell.org/rGHCbb84ee44e30e > | > | EMAIL PREFERENCES > | https://phabricator.haskell.org/settings/panel/emailpreferences/ > | > | To: simonpj, Harbormaster > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Mon Jun 27 08:01:28 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 27 Jun 2016 09:01:28 +0100 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: On 26 June 2016 at 11:28, Christopher Done wrote: > I've been pondering how feasible it would be to: > > * Compile in stages a module with the byte code linker > * Keep hold of the Core source > * Interpret the Core AST within Haskell > Interestingly, the first implementation of GHCi was a Core interpreter, but it ran into a lot of problems. For starters it would have unsafeCoerce everywhere. Support for unboxed values is very very difficult. > * When encountering built-in/primitives (or things from other libraries), > we compile that Core term and link it as an HValue and then run it with the > arguments expected. So () would be such a HValue, as would be "show" which > in interpretable unoptimized Core would take an extra argument for the Show > instance. When passing in values to such "foreign" functions it would wrap > them up in an interpretive way. > > This is the hypothetical idea, it seems like it would yield a really > trivial way to write a new and interesting interpreter for GHC Haskell > without having to re-implement any prim ops, ready to work on regular > Haskell code. > > In my case, I would use this to write an interpreter which: > > * is not tagless, so we preserve type info > Not sure what you mean here. Your interpreter would be running on top of the same RTS with the same data representation, so it would have to use the same tagging and representation conventions as the rest of GHC > * allows top-level names to be redefined > This you could do with the extisting byte-code interpreter, by instead of linking Names directly you link to some runtime Name-lookup function. You would probably want to revert all CAFs when the code changes too; this is currently not implemented for byte code. > * when a function is applied, it checks the type of its arguments > Aha, but what if the arguments come from compiled code? GHC doesn't carry type information around at runtime, except that it is possible reconstruct types in a limited kind of way (this is what the GHC debugger does). Cheers Simon > Both of these are pretty much necessary for being able to do in-place > update of a running program while developing (a la Emacs or Smalltalk), and > type tags let us throw a regular Haskell exception of type error, a la > deferred type errors. It means in your running program, if you make a > mistake or forget to update one part, it doesn't bring the whole program > down with an RTS error or a segfault, maybe a handler in a thread (like a > server or a video game) throws an exception and the developer just updates > their code and tries again. > > I'd love support for something like this, but I'd rather not have to > re-create the world just to add this capability. Because it's really just > conceptually regular interpreted GHC Haskell plus type tags and updating, > it seems like it should be a small diff. > > Any input into this? How far away is GHC's current architecture from > supporting such a concept? > > Ciao! > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 27 08:01:28 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 27 Jun 2016 08:01:28 +0000 Subject: msys2 64 bit: help help! Message-ID: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> Friends, esp Tamar, I am in happy possession of a new Surface Book, running Windows 10, which is delightful - except that I can't make the msys64 installation work, which is crucial for GHC. Can any of you help? * I install it from here: https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/, which seems to be the canonical place. The actual 64-bit exe seems to be msys2-x86_64-20160205.exe. * Installation goes fine * But when I launch the "MinGW-w54 Win64 shell" from the Start menu, the screen flashes as if it is briefly putting up a window, but then the window disappears. * Each time I do this the task manager shows that there is another running 'mintty.exe'. But it has no visible window Does anyone have any idea what I can do or how I can investigate? I can't do any GHC development without this! Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Mon Jun 27 08:21:16 2016 From: david.macek.0 at gmail.com (David Macek) Date: Mon, 27 Jun 2016 10:21:16 +0200 Subject: msys2 64 bit: help help! In-Reply-To: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <7577a568-d462-b9c9-22ff-76b4a0edd516@gmail.com> On 27. 6. 2016 10:01, Simon Peyton Jones via ghc-devs wrote: > Friends, esp Tamar, > > I am in happy possession of a new Surface Book, running Windows 10, which is delightful – except that I can’t make the msys64 installation work, which is crucial for GHC. Can any of you help? > > · I install it from here: https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/, which seems to be the canonical place. The actual 64-bit exe seems to be msys2-x86_64-20160205.exe. > > · Installation goes fine > > · But when I launch the “MinGW-w54 Win64 shell” from the Start menu, the screen flashes as if it is briefly putting up a window, but then the window disappears. > > · Each time I do this the task manager shows that there is another running ‘mintty.exe’. But it has no visible window > > > > Does anyone have any idea what I can do or how I can investigate? I can’t do any GHC development without this! Hi. Please try `C:\msys64\usr\bin\mintty.exe -h always -` (incl. the trailing dash). You can also try `C:\msys64\usr\bin\bash.exe -li` in case the culprit is really mintty. -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From lukexipd at gmail.com Mon Jun 27 08:35:14 2016 From: lukexipd at gmail.com (Luke Iannini) Date: Mon, 27 Jun 2016 01:35:14 -0700 Subject: msys2 64 bit: help help! In-Reply-To: <7577a568-d462-b9c9-22ff-76b4a0edd516@gmail.com> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <7577a568-d462-b9c9-22ff-76b4a0edd516@gmail.com> Message-ID: Congrats Simon : ) I use precisely the same machine! While I haven't run into that particular problem, I do use an alternative console that might provide a workaround in case you keep running into trouble: http://cmder.net/ My setup log is here, which explains how to use Cmder with MSYS2: https://gist.github.com/lukexi/e634067f1d7e3a629988#cmder All the best Luke On Mon, Jun 27, 2016 at 1:21 AM, David Macek wrote: > On 27. 6. 2016 10:01, Simon Peyton Jones via ghc-devs wrote: > > Friends, esp Tamar, > > > > I am in happy possession of a new Surface Book, running Windows 10, > which is delightful – except that I can’t make the msys64 installation > work, which is crucial for GHC. Can any of you help? > > > > · I install it from here: > https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/, which seems > to be the canonical place. The actual 64-bit exe seems to be > msys2-x86_64-20160205.exe. > > > > · Installation goes fine > > > > · But when I launch the “MinGW-w54 Win64 shell” from the Start > menu, the screen flashes as if it is briefly putting up a window, but then > the window disappears. > > > > · Each time I do this the task manager shows that there is > another running ‘mintty.exe’. But it has no visible window > > > > > > > > Does anyone have any idea what I can do or how I can investigate? I > can’t do any GHC development without this! > > Hi. > > Please try `C:\msys64\usr\bin\mintty.exe -h always -` (incl. the trailing > dash). You can also try `C:\msys64\usr\bin\bash.exe -li` in case the > culprit is really mintty. > > > -- > David Macek > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From chrisdone at gmail.com Mon Jun 27 12:06:58 2016 From: chrisdone at gmail.com (Christopher Done) Date: Mon, 27 Jun 2016 14:06:58 +0200 Subject: Using the GHC API to write an interpreter In-Reply-To: <1466992830-sup-1776@sabre> References: <1466992830-sup-1776@sabre> Message-ID: On 27 June 2016 at 04:11, Edward Z. Yang wrote: > I don't understand what the bytecode format has to do here. Since > your suggestion is to just store Core you can just compile to object > code. True, I could compile to either as long as I can link it dynamically. > > Any input into this? How far away is GHC's current architecture from > > supporting such a concept? > > Well, if you are going to support update you need to make sure that the > tag information is more elaborate than what GHC currently supports > (a type would just be a Name, which is going to get reused when you > recompile.) Indeed -- like in GHCi when you redefine a named thing, I'd hope to implement an incrementing Name[n] versioning for names. But Core's AST is trivial so it'd be easy to make this kind of transformation. From chrisdone at gmail.com Mon Jun 27 12:31:24 2016 From: chrisdone at gmail.com (Christopher Done) Date: Mon, 27 Jun 2016 14:31:24 +0200 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: On 27 June 2016 at 10:01, Simon Marlow wrote: > On 26 June 2016 at 11:28, Christopher Done wrote: >> >> I've been pondering how feasible it would be to: >> >> * Compile in stages a module with the byte code linker >> * Keep hold of the Core source >> * Interpret the Core AST within Haskell > > Interestingly, the first implementation of GHCi was a Core interpreter, but > it ran into a lot of problems. For starters it would have unsafeCoerce > everywhere. Support for unboxed values is very very difficult. What year is that implementation from? I wouldn't mind taking a look for it in the GHC repo history. >> * is not tagless, so we preserve type info > > Not sure what you mean here. Your interpreter would be running on top of > the same RTS with the same data representation, so it would have to use the > same tagging and representation conventions as the rest of GHC That's true, if a value comes from a compiled RTS function with a polymorphic type then I don't know what its real type is to marshal it properly. Drat. >> * allows top-level names to be redefined > > This you could do with the extisting byte-code interpreter, by instead of > linking Names directly you link to some runtime Name-lookup function. You > would probably want to revert all CAFs when the code changes too; this is > currently not implemented for byte code. Right, I considered this but without the type information it's going to blow up if I change the arity of a function or a data type or whatever. >> * when a function is applied, it checks the type of its arguments > > Aha, but what if the arguments come from compiled code? GHC doesn't carry > type information around at runtime, except that it is possible reconstruct > types in a limited kind of way (this is what the GHC debugger does). Indeed, from compiled code e.g. id then id (undefined :: Foo) would come back as something unidentifiable as being of type Foo. That's the flaw in my plan. Looks like the current interpreter would have to be extended to support this or a whole new one re-implementing all the primitives like in GHCJS. Thanks! From marlowsd at gmail.com Mon Jun 27 13:27:46 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 27 Jun 2016 14:27:46 +0100 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: On 27 June 2016 at 13:31, Christopher Done wrote: > On 27 June 2016 at 10:01, Simon Marlow wrote: > > On 26 June 2016 at 11:28, Christopher Done wrote: > >> > >> I've been pondering how feasible it would be to: > >> > >> * Compile in stages a module with the byte code linker > >> * Keep hold of the Core source > >> * Interpret the Core AST within Haskell > > > > Interestingly, the first implementation of GHCi was a Core interpreter, > but > > it ran into a lot of problems. For starters it would have unsafeCoerce > > everywhere. Support for unboxed values is very very difficult. > > What year is that implementation from? I wouldn't mind taking a look > for it in the GHC repo history. > > I think around here is a good place to start looking: https://phabricator.haskell.org/rGHCbca9dd54c2b39638cb4638aaccf6015a104a1df5#021fe2a9 Cheers Simon > >> * is not tagless, so we preserve type info > > > > Not sure what you mean here. Your interpreter would be running on top of > > the same RTS with the same data representation, so it would have to use > the > > same tagging and representation conventions as the rest of GHC > > That's true, if a value comes from a compiled RTS function with a > polymorphic type then I don't know what its real type is to marshal it > properly. Drat. > > >> * allows top-level names to be redefined > > > > This you could do with the extisting byte-code interpreter, by instead of > > linking Names directly you link to some runtime Name-lookup function. > You > > would probably want to revert all CAFs when the code changes too; this is > > currently not implemented for byte code. > > Right, I considered this but without the type information it's going > to blow up if I change the arity of a function or a data type or > whatever. > > >> * when a function is applied, it checks the type of its arguments > > > > Aha, but what if the arguments come from compiled code? GHC doesn't > carry > > type information around at runtime, except that it is possible > reconstruct > > types in a limited kind of way (this is what the GHC debugger does). > > Indeed, from compiled code e.g. id then id (undefined :: Foo) would > come back as something unidentifiable as being of type Foo. That's the > flaw in my plan. > > Looks like the current interpreter would have to be extended to > support this or a whole new one re-implementing all the primitives like > in GHCJS. > > Thanks! > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 27 21:33:40 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 27 Jun 2016 21:33:40 +0000 Subject: msys2 64 bit: help help! In-Reply-To: <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> Message-ID: <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> Tamar Thank you! Yes, it's in c:/msys64 Since I wrote more odd things have happened. 1. I just left the machine for 10-15 mins and lo! the shell windows opened up. It just took a loooong time. At this point, starting a new shell no longer took a long time. It all seemed to be working. 2. I then ran pacman -Syuu as instructed on the installation page: https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ The log of what happened is below. There are numerous failures involving Cygwin, which I do not have installed, at least not so far as I know. I do not know if these failures matter. 3. After this step, starting a shell failed altogether with "c:/msys64/mingw64_shell.bat is not recognised as an internal or external command". And sure enough, there is no such file. Presumably it existed in step 1. So perhaps step 2 deleted it? 4. As you mention, I then tried msys2_shell.cmd. It worked -- with a noticeable delay of 5 seconds or so. So I'm less stuck than before but * should I worry about all those install errs * how can I debug what's happening with that long delay * Should I nuke the start menu shortcuts that the msys64 installer so carefully installed in favour of msys2_shell.cmd? Thanks Simon pacman -Syuu :: Synchronising package databases... mingw32 277.4 KiB 501K/s 00:01 [#####################] 100% mingw32.sig 96.0 B 0.00B/s 00:00 [#####################] 100% mingw64 277.0 KiB 481K/s 00:01 [#####################] 100% mingw64.sig 96.0 B 0.00B/s 00:00 [#####################] 100% msys 134.9 KiB 2014K/s 00:00 [#####################] 100% msys.sig 96.0 B 0.00B/s 00:00 [#####################] 100% :: Starting full system upgrade... :: Replace repman-git with msys/pactoys-git? [Y/n] y resolving dependencies... looking for conflicting packages... Packages (41) bash-completion-2.3-1 bsdcpio-3.2.0-1 bsdtar-3.2.0-1 coreutils-8.25-1 crypt-1.3-1 curl-7.49.1-1 file-5.25-1 filesystem-2016.05-3 gcc-libs-5.3.0-3 gettext-0.19.7-3 gmp-6.1.0-2 gnupg-1.4.20-1 grep-2.22-3 gzip-1.7-1 heimdal-libs-1.5.3-9 libarchive-3.2.0-1 libasprintf-0.19.7-3 libassuan-2.4.2-1 libcrypt-1.3-1 libcurl-7.49.1-1 libexpat-2.1.1-1 libgettextpo-0.19.7-3 libgpg-error-1.21-1 libgpgme-1.6.0-1 libintl-0.19.7-3 liblzma-5.2.2-1 libnettle-3.2-1 libopenssl-1.0.2.h-1 libssh2-1.7.0-1 mintty-1~2.2.3-1 mpfr-3.1.4-1 msys2-launcher-git-0.3.29.4028b6c-1 msys2-runtime-2.5.1-1 ncurses-6.0.20160220-1 openssl-1.0.2.h-1 pacman-5.0.1.6403.520736d-1 pactoys-git-r1.e58a7ac-1 rebase-4.4.2-1 repman-git-r23.87bf865-1 [removal] wget-1.17.1-3 xz-5.2.2-1 Total Download Size: 24.85 MiB Total Installed Size: 124.28 MiB Net Upgrade Size: 6.09 MiB :: Proceed with installation? [Y/n] y :: Retrieving packages ... msys2-runtime-2.5.1... 2.2 MiB 912K/s 00:03 [#####################] 100% bash-completion-2.3... 184.1 KiB 4.50M/s 00:00 [#####################] 100% gcc-libs-5.3.0-3-x86_64 783.6 KiB 1818K/s 00:00 [#####################] 100% libintl-0.19.7-3-x86_64 25.6 KiB 3.13M/s 00:00 [#####################] 100% libgettextpo-0.19.7... 110.7 KiB 3.60M/s 00:00 [#####################] 100% libasprintf-0.19.7-... 11.8 KiB 1686K/s 00:00 [#####################] 100% gettext-0.19.7-3-x86_64 1524.1 KiB 1774K/s 00:01 [#####################] 100% liblzma-5.2.2-1-x86_64 76.6 KiB 6.23M/s 00:00 [#####################] 100% gmp-6.1.0-2-x86_64 369.2 KiB 2.03M/s 00:00 [#####################] 100% libnettle-3.2-1-x86_64 101.1 KiB 5.20M/s 00:00 [#####################] 100% coreutils-8.25-1-x86_64 2.2 MiB 1794K/s 00:01 [#####################] 100% ncurses-6.0.2016022... 1147.2 KiB 1833K/s 00:01 [#####################] 100% bsdcpio-3.2.0-1-x86_64 747.1 KiB 2.08M/s 00:00 [#####################] 100% bsdtar-3.2.0-1-x86_64 785.4 KiB 1879K/s 00:00 [#####################] 100% libcrypt-1.3-1-x86_64 13.5 KiB 1692K/s 00:00 [#####################] 100% crypt-1.3-1-x86_64 13.9 KiB 1979K/s 00:00 [#####################] 100% libopenssl-1.0.2.h-... 803.0 KiB 1921K/s 00:00 [#####################] 100% heimdal-libs-1.5.3-... 592.7 KiB 1976K/s 00:00 [#####################] 100% openssl-1.0.2.h-1-x... 1354.4 KiB 1929K/s 00:01 [#####################] 100% gzip-1.7-1-x86_64 97.0 KiB 3.16M/s 00:00 [#####################] 100% libssh2-1.7.0-1-x86_64 170.7 KiB 2.69M/s 00:00 [#####################] 100% libexpat-2.1.1-1-x86_64 56.9 KiB 3.27M/s 00:00 [#####################] 100% libcurl-7.49.1-1-x86_64 191.1 KiB 1855K/s 00:00 [#####################] 100% curl-7.49.1-1-x86_64 608.4 KiB 627K/s 00:01 [#####################] 100% file-5.25-1-x86_64 396.5 KiB 352K/s 00:01 [#####################] 100% filesystem-2016.05-... 36.3 KiB 1297K/s 00:00 [#####################] 100% gnupg-1.4.20-1-x86_64 1026.9 KiB 1927K/s 00:01 [#####################] 100% grep-2.22-3-x86_64 230.3 KiB 2.29M/s 00:00 [#####################] 100% libarchive-3.2.0-1-... 743.4 KiB 2.09M/s 00:00 [#####################] 100% mintty-1~2.2.3-1-x86_64 147.2 KiB 4.64M/s 00:00 [#####################] 100% mpfr-3.1.4-1-x86_64 238.5 KiB 1099K/s 00:00 [#####################] 100% msys2-launcher-git-... 28.5 KiB 2037K/s 00:00 [#####################] 100% xz-5.2.2-1-x86_64 142.5 KiB 3.87M/s 00:00 [#####################] 100% pacman-5.0.1.6403.5... 6.8 MiB 1776K/s 00:04 [#####################] 100% rebase-4.4.2-1-x86_64 236.4 KiB 1487K/s 00:00 [#####################] 100% libgpg-error-1.21-1... 103.8 KiB 3.38M/s 00:00 [#####################] 100% libassuan-2.4.2-1-x... 91.7 KiB 4.71M/s 00:00 [#####################] 100% libgpgme-1.6.0-1-x86_64 175.7 KiB 4.09M/s 00:00 [#####################] 100% wget-1.17.1-3-x86_64 570.7 KiB 2.04M/s 00:00 [#####################] 100% pactoys-git-r1.e58a... 27.7 KiB 3.00M/s 00:00 [#####################] 100% (40/40) checking keys in keyring [#####################] 100% (40/40) checking package integrity [#####################] 100% (40/40) loading package files [#####################] 100% (40/40) checking for file conflicts [#####################] 100% (41/41) checking available disk space [#####################] 100% warning: could not get file information for mingw32/ warning: could not get file information for mingw32/bin/ warning: could not get file information for mingw32/etc/ warning: could not get file information for mingw32/include/ warning: could not get file information for mingw32/lib/ warning: could not get file information for mingw32/share/ warning: could not get file information for mingw64/ warning: could not get file information for mingw64/bin/ warning: could not get file information for mingw64/etc/ warning: could not get file information for mingw64/include/ warning: could not get file information for mingw64/lib/ warning: could not get file information for mingw64/share/ warning: could not get file information for opt/ warning: could not get file information for mingw32.exe warning: could not get file information for mingw32.ini warning: could not get file information for mingw64.exe warning: could not get file information for mingw64.ini warning: could not get file information for msys2.exe warning: could not get file information for msys2.ini warning: could not get file information for autorebasebase1st.bat :: Processing package changes... (1/1) removing repman-git [#####################] 100% ( 1/40) upgrading msys2-runtime [#####################] 100% ( 2/40) upgrading bash-completion [#####################] 100% ( 3/40) upgrading gcc-libs [#####################] 100% 3 [main] pacman (8492) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 0 [main] pacman 6424 fork: child -1 - forked process 8492 died unexpectedl y, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) ( 4/40) upgrading libintl [#####################] 100% ( 5/40) upgrading libgettextpo [#####################] 100% ( 6/40) upgrading libasprintf [#####################] 100% ( 7/40) upgrading gettext [#####################] 100% 1 [main] pacman (700) C:\msys64\usr\bin\pacman.exe: *** fatal error - cygh eap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 1793360 [main] pacman 6424 fork: child -1 - forked process 700 died unexpectedly , retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) ( 8/40) upgrading liblzma [#####################] 100% ( 9/40) upgrading gmp [#####################] 100% 1 [main] pacman (3128) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 1942064 [main] pacman 6424 fork: child -1 - forked process 3128 died unexpectedl y, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (10/40) upgrading libnettle [#####################] 100% (11/40) upgrading coreutils [#####################] 100% 1 [main] pacman (3376) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 4846481 [main] pacman 6424 fork: child -1 - forked process 3376 died unexpectedl y, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (12/40) upgrading ncurses [#####################] 100% (13/40) upgrading bsdcpio [#####################] 100% (14/40) upgrading bsdtar [#####################] 100% (15/40) upgrading libcrypt [#####################] 100% (16/40) upgrading crypt [#####################] 100% (17/40) upgrading libopenssl [#####################] 100% (18/40) upgrading heimdal-libs [#####################] 100% (19/40) upgrading openssl [#####################] 100% (20/40) upgrading gzip [#####################] 100% 1 [main] pacman (1752) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 24726165 [main] pacman 6424 fork: child -1 - forked process 1752 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (21/40) upgrading libssh2 [#####################] 100% (22/40) upgrading libexpat [#####################] 100% (23/40) upgrading libcurl [#####################] 100% (24/40) upgrading curl [#####################] 100% (25/40) upgrading file [#####################] 100% (26/40) upgrading filesystem [#####################] 100% 1 [main] pacman (6260) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 27083623 [main] pacman 6424 fork: child -1 - forked process 6260 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (27/40) upgrading gnupg [#####################] 100% 1 [main] pacman (852) C:\msys64\usr\bin\pacman.exe: *** fatal error - cygh eap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 27485279 [main] pacman 6424 fork: child -1 - forked process 852 died unexpectedl y, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (28/40) upgrading grep [#####################] 100% 2 [main] pacman (3868) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 27800784 [main] pacman 6424 fork: child -1 - forked process 3868 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (29/40) upgrading libarchive [#####################] 100% (30/40) upgrading mintty [#####################] 100% (31/40) upgrading mpfr [#####################] 100% 1 [main] pacman (4728) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 28144605 [main] pacman 6424 fork: child -1 - forked process 4728 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (32/40) upgrading msys2-launcher-git [#####################] 100% (33/40) upgrading xz [#####################] 100% (34/40) upgrading pacman [#####################] 100% (35/40) upgrading rebase [#####################] 100% (36/40) installing libgpg-error [#####################] 100% (37/40) installing libassuan [#####################] 100% 1 [main] pacman (4672) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 31924467 [main] pacman 6424 fork: child -1 - forked process 4672 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (38/40) installing libgpgme [#####################] 100% 1 [main] pacman (5432) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 32015724 [main] pacman 6424 fork: child -1 - forked process 5432 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) (39/40) installing wget [#####################] 100% 1 [main] pacman (9128) C:\msys64\usr\bin\pacman.exe: *** fatal error - cyg heap base mismatch detected - 0x180326400/0x18033A400. This problem is probably due to using incompatible versions of the cygwin DLL. Search for cygwin1.dll using the Windows Start->Find/Search facility and delete all but the most recent version. The most recent version *should* reside in x:\cygwin\bin, where 'x' is the drive on which you have installed the cygwin distribution. Rebooting is also suggested if you are unable to find another cygwin DLL. 32712616 [main] pacman 6424 fork: child -1 - forked process 9128 died unexpected ly, retry 0, exit code 0xC0000142, errno 11 error: could not fork a new process (Resource temporarily unavailable) Optional dependencies for wget ca-certificates: HTTPS downloads [installed] (40/40) installing pactoys-git [#####################] 100% -----Original Message----- From: Tamar Christina [mailto:tamar at zhox.com] Sent: 27 June 2016 09:19 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: Re: msys2 64 bit: help help! Hi Simon, Did you install it to the default location (C:\Msys64) or to a location with spaces in the path? The Msys2 stuff is quite particular about spaces in the path. If that's not the case, then in the install location of msys2 you should find 3 batch files (mingw32.bat, mingw64.bat and msys2_shell.bat) If you only have the msys2_shell.bat use that one instead of mingw64.bat (msys2 in an update will change the shortcuts so I am not sure if the update was done already on your install). Open a command-line window and run that batch file. It should then show you the error without closing the window. alternatively, you can try starting bash in cmd instead of mitty, using "set MSYSTEM=MINGW64 && E:\msys64 E:\msys64\usr\bin\bash --login" replacing the path with your install path. Let me know if these don't work. Kind Regards, Tamar 3 batch files ---- On Mon, 27 Jun 2016 10:01:28 +0200 Simon Peyton Jones wrote ---- > Friends, esp Tamar, > > I am in happy possession of a new Surface Book, running Windows 10, which is delightful – except that I can’t make the msys64 installation work, which is crucial for GHC. Can any of you help? > > · I install it from here: https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fsourceforge.net%2fp%2fmsys2%2fwiki%2fMSYS2%2520installation%2f&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c2801115a7b2e43ebd2da08d39e63ba89%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=qXzbQdt3AGrhl3oL48tbGsUgpz%2b6q9uCCMrlfn145Wg%3d, which seems to be the canonical place. The actual 64-bit exe seems to be msys2-x86_64-20160205.exe. > · Installation goes fine > · But when I launch the “MinGW-w54 Win64 shell” from the Start menu, the screen flashes as if it is briefly putting up a window, but then the window disappears. > · Each time I do this the task manager shows that there is another running ‘mintty.exe’. But it has no visible window > > Does anyone have any idea what I can do or how I can investigate? I can’t do any GHC development without this! > > Thanks > > Simon > > > > From andrey.mokhov at newcastle.ac.uk Mon Jun 27 21:59:36 2016 From: andrey.mokhov at newcastle.ac.uk (Andrey Mokhov) Date: Mon, 27 Jun 2016 21:59:36 +0000 Subject: msys2 64 bit: help help! Message-ID: Hi Simon, > 3. After this step, starting a shell failed altogether with "c:/msys64/mingw64_shell.bat is > not recognised as an internal or external command". And sure enough, there is no such file. > Presumably it existed in step 1. So perhaps step 2 deleted it? > [...] > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with a noticeable delay of 5 > seconds or so. I've also just got a new Win10 laptop and had the same issue with missing mingw64_shell.bat during msys2 install. I solved it by creating mingw64.bat with the following contents: msys2_shell.cmd -mingw64 -mintty I deleted all old shortcuts and use this script instead. Everything seems to work fine -- can build GHC. Cheers, Andrey From lonetiger at gmail.com Mon Jun 27 22:44:17 2016 From: lonetiger at gmail.com (Phyx) Date: Mon, 27 Jun 2016 23:44:17 +0100 Subject: msys2 64 bit: help help! In-Reply-To: References: Message-ID: Hi Simon, Andrey > > 3. After this step, starting a shell failed altogether with > "c:/msys64/mingw64_shell.bat is > > not recognised as an internal or external command". And sure enough, > there is no such file. > > Presumably it existed in step 1. So perhaps step 2 deleted it? > > [...] > > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with a > noticeable delay of 5 > > seconds or so. > > I've also just got a new Win10 laptop and had the same issue with missing > mingw64_shell.bat during msys2 install. I solved it by creating mingw64.bat > with the following contents: > > msys2_shell.cmd -mingw64 -mintty > > I deleted all old shortcuts and use this script instead. Everything seems > to work fine -- can build GHC. > > Yes this is correct, the msys2 team has decided to "streamline" all their different batch files to launch msys from 4 to 1, hence the only remaining one is msys2_shell.cmd which accepts arguments of which shell to open and using which console host. Unfortunately this is done via their upgrade-core script and doesn't know how to remove the installer shortcuts, so you end up with dead shortcuts. > 1. I just left the machine for 10-15 mins and lo! the shell windows opened up. It just took a loooong time. > > At this point, starting a new shell no longer took a long time. It all seemed to be working. First launch should be finishing setting up the environment so will take slightly longer, but shouldn't have taken that long. Could this be AV related? I always add an exception to the AV (or the build in windows defender) for the msys2 folder to prevent it from scanning files continuously. Especially building GHC this can slow things down considerably depending on the AV. > 2. I then ran pacman -Syuu as instructed on the installation page: https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ > > The log of what happened is below. There are numerous failures involving Cygwin, which I do not have installed, at least not so far as I know. I do not know if these failures matter. These instructions are basically telling it to upgrade the world. They are however a bit wrong, https://github.com/Alexpux/MSYS2-packages/issues/373 msys2 is derived from Cygwin so it inherits much of the problems of Cygwin. The msys2 runtime is the Cygwin runtime with patches added which is why the errors mention Cygwin. The issue is that the msys2-runtime has been upgraded by "pacman -Syuu" at which point a new "Cygwin" dll has been downloaded. However all Cygwin/msys2 runtimes share the same address space and thus you can't have multiple versions of the same runtime loaded at once. This is why subsequent calls to anything relying on the msys2 runtime will fail with a weird fork error. The solution is to just close all open msys2 window and re-open. Our own instructions page https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows breaks this down in a few steps to avoid this issue. 1) first update the packages and 2) only after that update the msys-core files. But you will still need to restart the shell. > * should I worry about all those install errs No they're perfectly fine and expected. I would however re-run the pacman -Syu to make sure all packages were updated, now that the runtime has been updated already it shouldn't be updated again and you shouldn't see any fork errors. > * how can I debug what's happening with > that long delay If it's only startup and not executing of other commands or bash completion then my bet would be AV software. If bash completion is slow or commands like ls as well you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. * Should I nuke the start menu shortcuts that the msys64 installer so carefully installed in favour of msys2_shell.cmd? Yes, these are now dead. you need to use msys2_shell.cmd but also pass it -mingw64 so it knows what shell to start. mintty is supposed to be the default, but in case that changes you can also pass it -mintty as well to be sure it doesn't change. I am working on a script to automate this setup, hopefully that would make it easier next time! Cheers, Tamar -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Tue Jun 28 12:19:34 2016 From: david.macek.0 at gmail.com (David Macek) Date: Tue, 28 Jun 2016 14:19:34 +0200 Subject: msys2 64 bit: help help! In-Reply-To: <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> On 27. 6. 2016 23:33, Simon Peyton Jones via ghc-devs wrote: > 1. I just left the machine for 10-15 mins and lo! the shell windows opened up. It just took a loooong time. I could be something with Active Directory. Cygwin (upon which is MSYS2 based) integrates with AD, but there are numerous (google-able) reports of huge slowdowns related to this. > At this point, starting a new shell no longer took a long time. It all seemed to be working. Also don't forget to exclude `C:\msys64` from any anti-virus scans. > 2. I then ran pacman -Syuu as instructed on the installation page: https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ I'm afraid you misread the instructions. You should run `update-core` first to upgrade to the newer pacman that handles `pacman -Syuu` correctly. (New installer packages with an up-to-date pacman are planned.) > The log of what happened is below. There are numerous failures involving Cygwin, which I do not have installed, at least not so far as I know. I do not know if these failures matter. They might. See below. > 3. After this step, starting a shell failed altogether with "c:/msys64/mingw64_shell.bat is not recognised as an internal or external command". And sure enough, there is no such file. Presumably it existed in step 1. So perhaps step 2 deleted it? If the post-install script for `filesystem` were able to run, it would inform you that `*_shell.bat` are deprecated and were removed. I see you have `msys2-launcher-git` installed -- you can then use `C:\msys64\mingw64.exe` (and even pin it to the taskbar). > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with a noticeable delay of 5 seconds or so. May still be AD-related. > * should I worry about all those install errs I recommend staying on the safe side and nuke the installation. Alternatively, reinstall the packages that had failures (`pacman -S gcc-libs gettext gmp ...`). > * how can I debug what's happening with > that long delay `/etc/nsswitch.conf` allows for some configuration. See . > * Should I nuke the start menu shortcuts that > the msys64 installer so carefully installed > in favour of msys2_shell.cmd? Yes or see above. Note that you might need `msys2_shell.cmd -mingw64` instead (not sure if it matters for GHC). -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From simonpj at microsoft.com Tue Jun 28 12:47:18 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 28 Jun 2016 12:47:18 +0000 Subject: msys2 64 bit: help help! In-Reply-To: <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> Message-ID: <461fa2fd6aee4d60ad42e4ac335ce842@DB4PR30MB030.064d.mgd.msft.net> David, Tamar Thanks for your help. I'm a bit further forward. | > 1. I just left the machine for 10-15 mins and lo! the shell windows | opened up. It just took a loooong time. | | I could be something with Active Directory. Cygwin (upon which is | MSYS2 based) integrates with AD, but there are numerous (google-able) | reports of huge slowdowns related to this. | > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with | a noticeable delay of 5 seconds or so. | | May still be AD-related. Let's suppose it is AD. Do you have any idea what I can do about it? | If the post-install script for `filesystem` were able to run, it would | inform you that `*_shell.bat` are deprecated and were removed. I see | you have `msys2-launcher-git` installed -- you can then use | `C:\msys64\mingw64.exe` (and even pin it to the taskbar). OK... so forget msys2_shell.cmd and use mingw64.exe instead. I'll try that. | > * how can I debug what's happening with | > that long delay | | `/etc/nsswitch.conf` allows for some configuration. See | . OK.. I see that page. Now what? What might I do with nsswitch.conf that might help fix or give insight? Simon From simonpj at microsoft.com Tue Jun 28 12:50:59 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 28 Jun 2016 12:50:59 +0000 Subject: msys2 64 bit: help help! In-Reply-To: <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> Message-ID: <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> David, Tamar I have another issue. I'm using 'magit' (in emacs) to drive git. But it gives half-minute delays to do anything at all. There are lots of people complaining about it (googlable) but no solutions I can see. Do I have to give up magit? It used to be fine in earlier versions. Just at the moment it's Much Much More Serious. Even opening a file in emacs (nothing to do with git or (ostensibly) magit, takes nearly a minute!! In the process manager I can see lots of git activity -- just when I open a file in ordinary emacs! I have utterly no idea why this might be. I'm adding John Wiegley, my Emacs Friend Thanks Simon | -----Original Message----- | From: David Macek [mailto:david.macek.0 at gmail.com] | Sent: 28 June 2016 13:20 | To: Simon Peyton Jones ; tamar at zhox.com | Cc: ghc-devs at haskell.org | Subject: Re: msys2 64 bit: help help! | | On 27. 6. 2016 23:33, Simon Peyton Jones via ghc-devs wrote: | > 1. I just left the machine for 10-15 mins and lo! the shell windows | opened up. It just took a loooong time. | | I could be something with Active Directory. Cygwin (upon which is | MSYS2 based) integrates with AD, but there are numerous (google-able) | reports of huge slowdowns related to this. | | > At this point, starting a new shell no longer took a long time. It | all seemed to be working. | | Also don't forget to exclude `C:\msys64` from any anti-virus scans. | | | > 2. I then ran pacman -Syuu as instructed on the installation page: | https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ | | I'm afraid you misread the instructions. You should run `update-core` | first to upgrade to the newer pacman that handles `pacman -Syuu` | correctly. (New installer packages with an up-to-date pacman are | planned.) | | > The log of what happened is below. There are numerous failures | involving Cygwin, which I do not have installed, at least not so far | as I know. I do not know if these failures matter. | | They might. See below. | | > 3. After this step, starting a shell failed altogether with | "c:/msys64/mingw64_shell.bat is not recognised as an internal or | external command". And sure enough, there is no such file. Presumably | it existed in step 1. So perhaps step 2 deleted it? | | If the post-install script for `filesystem` were able to run, it would | inform you that `*_shell.bat` are deprecated and were removed. I see | you have `msys2-launcher-git` installed -- you can then use | `C:\msys64\mingw64.exe` (and even pin it to the taskbar). | | > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with | a noticeable delay of 5 seconds or so. | | May still be AD-related. | | > * should I worry about all those install errs | | I recommend staying on the safe side and nuke the installation. | Alternatively, reinstall the packages that had failures (`pacman -S | gcc-libs gettext gmp ...`). | | > * how can I debug what's happening with | > that long delay | | `/etc/nsswitch.conf` allows for some configuration. See | . | | > * Should I nuke the start menu shortcuts that | > the msys64 installer so carefully installed | > in favour of msys2_shell.cmd? | | Yes or see above. Note that you might need `msys2_shell.cmd -mingw64` | instead (not sure if it matters for GHC). | | -- | David Macek From lonetiger at gmail.com Tue Jun 28 13:54:29 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Tue, 28 Jun 2016 14:54:29 +0100 Subject: msys2 64 bit: help help! In-Reply-To: <461fa2fd6aee4d60ad42e4ac335ce842@DB4PR30MB030.064d.mgd.msft.net> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <461fa2fd6aee4d60ad42e4ac335ce842@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <57727385.4a79c20a.70674.0664@mx.google.com> Hi Simon, To test if it’s AD try (in case my other email didn’t get through): ➢ you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. Cheers, Tamar From: Simon Peyton Jones via ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From stegeman at gmail.com Tue Jun 28 13:09:25 2016 From: stegeman at gmail.com (Luite Stegeman) Date: Tue, 28 Jun 2016 13:09:25 +0000 Subject: msys2 64 bit: help help! In-Reply-To: <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Have you tried specifying an absolute path for the git executable that magit uses, to avoid the overhead of traversing the environment for each call? (M-x customize-var RET magit-git-executable RET) On Tue, Jun 28, 2016 at 2:51 PM Simon Peyton Jones via ghc-devs < ghc-devs at haskell.org> wrote: > David, Tamar > > I have another issue. I'm using 'magit' (in emacs) to drive git. But it > gives half-minute delays to do anything at all. There are lots of people > complaining about it (googlable) but no solutions I can see. Do I have to > give up magit? > > It used to be fine in earlier versions. > > Just at the moment it's Much Much More Serious. Even opening a file in > emacs (nothing to do with git or (ostensibly) magit, takes nearly a > minute!! In the process manager I can see lots of git activity -- just > when I open a file in ordinary emacs! > > I have utterly no idea why this might be. I'm adding John Wiegley, my > Emacs Friend > > Thanks > > Simon > > | -----Original Message----- > | From: David Macek [mailto:david.macek.0 at gmail.com] > | Sent: 28 June 2016 13:20 > | To: Simon Peyton Jones ; tamar at zhox.com > | Cc: ghc-devs at haskell.org > | Subject: Re: msys2 64 bit: help help! > | > | On 27. 6. 2016 23:33, Simon Peyton Jones via ghc-devs wrote: > | > 1. I just left the machine for 10-15 mins and lo! the shell windows > | opened up. It just took a loooong time. > | > | I could be something with Active Directory. Cygwin (upon which is > | MSYS2 based) integrates with AD, but there are numerous (google-able) > | reports of huge slowdowns related to this. > | > | > At this point, starting a new shell no longer took a long time. It > | all seemed to be working. > | > | Also don't forget to exclude `C:\msys64` from any anti-virus scans. > | > | > | > 2. I then ran pacman -Syuu as instructed on the installation page: > | https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ > | > | I'm afraid you misread the instructions. You should run `update-core` > | first to upgrade to the newer pacman that handles `pacman -Syuu` > | correctly. (New installer packages with an up-to-date pacman are > | planned.) > | > | > The log of what happened is below. There are numerous failures > | involving Cygwin, which I do not have installed, at least not so far > | as I know. I do not know if these failures matter. > | > | They might. See below. > | > | > 3. After this step, starting a shell failed altogether with > | "c:/msys64/mingw64_shell.bat is not recognised as an internal or > | external command". And sure enough, there is no such file. Presumably > | it existed in step 1. So perhaps step 2 deleted it? > | > | If the post-install script for `filesystem` were able to run, it would > | inform you that `*_shell.bat` are deprecated and were removed. I see > | you have `msys2-launcher-git` installed -- you can then use > | `C:\msys64\mingw64.exe` (and even pin it to the taskbar). > | > | > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with > | a noticeable delay of 5 seconds or so. > | > | May still be AD-related. > | > | > * should I worry about all those install errs > | > | I recommend staying on the safe side and nuke the installation. > | Alternatively, reinstall the packages that had failures (`pacman -S > | gcc-libs gettext gmp ...`). > | > | > * how can I debug what's happening with > | > that long delay > | > | `/etc/nsswitch.conf` allows for some configuration. See > | | pwdgrp>. > | > | > * Should I nuke the start menu shortcuts that > | > the msys64 installer so carefully installed > | > in favour of msys2_shell.cmd? > | > | Yes or see above. Note that you might need `msys2_shell.cmd -mingw64` > | instead (not sure if it matters for GHC). > | > | -- > | David Macek > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Tue Jun 28 13:21:43 2016 From: david.macek.0 at gmail.com (David Macek) Date: Tue, 28 Jun 2016 15:21:43 +0200 Subject: msys2 64 bit: help help! In-Reply-To: References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <0b8a6c9d-ae27-3fb9-3089-4b6bdb54631e@gmail.com> > I have another issue. I'm using 'magit' (in emacs) to drive git. But it gives half-minute delays to do anything at all. There are lots of people complaining about it (googlable) but no solutions I can see. Do I have to give up magit? I've read about it too, but I don't remember seeing any solutions. I don't use magit nor emacs, but I have two ideas: a) Try `mingw-w64-x86_64-emacs` (through pacman) with `mingw-w64-x86_64-git` (download[2] or through pacman[1]). This should work around any performance issues coming from the POSIX emulation layer. The downside is that I have no idea whether this combination works well currently (or at all). b) `git config core.fscache true`. I'm not sure if this option is supported under Cygwin. [1] [2] -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From simonpj at microsoft.com Tue Jun 28 15:00:45 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 28 Jun 2016 15:00:45 +0000 Subject: msys2 64 bit: help help! In-Reply-To: References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> Message-ID: Have you tried specifying an absolute path for the git executable that magit uses, to avoid the overhead of traversing the environment for each call? (M-x customize-var RET magit-git-executable RET) I’m pretty sure it’s not that, because in the task manager I see stuck ‘git.exe’ consuming zero cycles with a child process of ‘comhost’ (I think). Then it completes and another one is born. But I’ll give it a try anyway, thanks I’m still utterly baffled about why emacs is invoking git when I simply open a file (Ctrl-X f). Simon From: Luite Stegeman [mailto:stegeman at gmail.com] Sent: 28 June 2016 14:09 To: Simon Peyton Jones ; David Macek ; tamar at zhox.com; John Wiegley Cc: ghc-devs at haskell.org Subject: Re: msys2 64 bit: help help! Have you tried specifying an absolute path for the git executable that magit uses, to avoid the overhead of traversing the environment for each call? (M-x customize-var RET magit-git-executable RET) On Tue, Jun 28, 2016 at 2:51 PM Simon Peyton Jones via ghc-devs > wrote: David, Tamar I have another issue. I'm using 'magit' (in emacs) to drive git. But it gives half-minute delays to do anything at all. There are lots of people complaining about it (googlable) but no solutions I can see. Do I have to give up magit? It used to be fine in earlier versions. Just at the moment it's Much Much More Serious. Even opening a file in emacs (nothing to do with git or (ostensibly) magit, takes nearly a minute!! In the process manager I can see lots of git activity -- just when I open a file in ordinary emacs! I have utterly no idea why this might be. I'm adding John Wiegley, my Emacs Friend Thanks Simon | -----Original Message----- | From: David Macek [mailto:david.macek.0 at gmail.com] | Sent: 28 June 2016 13:20 | To: Simon Peyton Jones >; tamar at zhox.com | Cc: ghc-devs at haskell.org | Subject: Re: msys2 64 bit: help help! | | On 27. 6. 2016 23:33, Simon Peyton Jones via ghc-devs wrote: | > 1. I just left the machine for 10-15 mins and lo! the shell windows | opened up. It just took a loooong time. | | I could be something with Active Directory. Cygwin (upon which is | MSYS2 based) integrates with AD, but there are numerous (google-able) | reports of huge slowdowns related to this. | | > At this point, starting a new shell no longer took a long time. It | all seemed to be working. | | Also don't forget to exclude `C:\msys64` from any anti-virus scans. | | | > 2. I then ran pacman -Syuu as instructed on the installation page: | https://sourceforge.net/p/msys2/wiki/MSYS2%20installation/ | | I'm afraid you misread the instructions. You should run `update-core` | first to upgrade to the newer pacman that handles `pacman -Syuu` | correctly. (New installer packages with an up-to-date pacman are | planned.) | | > The log of what happened is below. There are numerous failures | involving Cygwin, which I do not have installed, at least not so far | as I know. I do not know if these failures matter. | | They might. See below. | | > 3. After this step, starting a shell failed altogether with | "c:/msys64/mingw64_shell.bat is not recognised as an internal or | external command". And sure enough, there is no such file. Presumably | it existed in step 1. So perhaps step 2 deleted it? | | If the post-install script for `filesystem` were able to run, it would | inform you that `*_shell.bat` are deprecated and were removed. I see | you have `msys2-launcher-git` installed -- you can then use | `C:\msys64\mingw64.exe` (and even pin it to the taskbar). | | > 4. As you mention, I then tried msys2_shell.cmd. It worked -- with | a noticeable delay of 5 seconds or so. | | May still be AD-related. | | > * should I worry about all those install errs | | I recommend staying on the safe side and nuke the installation. | Alternatively, reinstall the packages that had failures (`pacman -S | gcc-libs gettext gmp ...`). | | > * how can I debug what's happening with | > that long delay | | `/etc/nsswitch.conf` allows for some configuration. See | | pwdgrp>. | | > * Should I nuke the start menu shortcuts that | > the msys64 installer so carefully installed | > in favour of msys2_shell.cmd? | | Yes or see above. Note that you might need `msys2_shell.cmd -mingw64` | instead (not sure if it matters for GHC). | | -- | David Macek _______________________________________________ ghc-devs mailing list ghc-devs at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon at joyful.com Tue Jun 28 17:09:32 2016 From: simon at joyful.com (Simon Michael) Date: Tue, 28 Jun 2016 10:09:32 -0700 Subject: msys2 64 bit: help help! In-Reply-To: <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <4e29a444-7999-f0c0-5cf4-7f11ed5367ff@joyful.com> On 6/28/16 5:50 AM, Simon Peyton Jones via ghc-devs wrote: > I have another issue. I'm using 'magit' (in emacs) to drive git. But it gives half-minute delays to do anything at all. There are lots of people complaining about it (googlable) but no solutions I can see. Do I have to give up magit? > > It used to be fine in earlier versions. > > Just at the moment it's Much Much More Serious. Even opening a file in emacs (nothing to do with git or (ostensibly) magit, takes nearly a minute!! In the process manager I can see lots of git activity -- just when I open a file in ordinary emacs! Hi Simon, I've never seen that behaviour, but if it's not active directory/network related, might you have enabled some add-on that eg tries to show a file's VCS status in the modeline ? Here are some things you may have already tried: - restart emacs - restart emacs with --no-init-file, then gradually evaluate your .emacs.d/init.el (and more specifically, any magit/vcs-related customizations) while testing magit performance. - close unnecessary open buffers visiting files in the current git repo. This might be contributing, in my setup it makes a big difference. I do C-x C-b s m to sort open buffers by mode, n/p to move to the haskell buffers, d to mark them deleted, x to do it. - look for and turn off costly magit settings, in M-x customize-group magit. I'm sorry that I don't know/remember which ones are costly. I would be suspicious of the two auto revert options and the Magit Extensions -> Magit Auto Revert group, and magit's hooks (Magit Modes -> *Hook). From lonetiger at gmail.com Tue Jun 28 20:14:52 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Tue, 28 Jun 2016 21:14:52 +0100 Subject: msys2 64 bit: help help! In-Reply-To: References: <58b10c8c37644ee6b6aa661632aa502d@DB4PR30MB030.064d.mgd.msft.net> <15590f0d2ea.c436edb31429.8508734420018797448@zhox.com> <3b614da4a510433b8187286c1654a19b@DB4PR30MB030.064d.mgd.msft.net> <4ee0023e-d2dc-3050-2759-bd9e6eb947a4@gmail.com> <2fe84f8749db472aa93c107150652583@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <5772ccac.c255c20a.e8518.4ab6@mx.google.com> Hi Simon, I think the two issues might be related. From what I can tell magit invokes some msys utilies at startup such as cygdrive to normalize paths https://github.com/magit/magit/issues/2284 . The msys AD issue would affect all of these tools and so each of them would be quite slow to run. I would indeed try the AD fix first and see how the rest behave. This issue is well documented at the Cygwin FAQ as well https://cygwin.com/faq/faq.html#faq.using.startup-slow if you’re interested in what’s Going on. Basically what it’s saying is that you can cache your user information (username etc) locally instead of having it query the server everytime. If this doesn’t solve the magit problem as well, then try issuing a normal git command, if that’s slow as well then run strace on it and it should give You an idea of what’s taking so long. Kind Regards, Tamar From: Simon Peyton Jones via ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From chrisdone at gmail.com Tue Jun 28 19:15:45 2016 From: chrisdone at gmail.com (Christopher Done) Date: Tue, 28 Jun 2016 21:15:45 +0200 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: Thanks! It's strange to think there was once no GHCi. This is an interesting piece of Haskell implementation history! =) On 27 June 2016 at 15:27, Simon Marlow wrote: > > > On 27 June 2016 at 13:31, Christopher Done wrote: > >> On 27 June 2016 at 10:01, Simon Marlow wrote: >> > On 26 June 2016 at 11:28, Christopher Done wrote: >> >> >> >> I've been pondering how feasible it would be to: >> >> >> >> * Compile in stages a module with the byte code linker >> >> * Keep hold of the Core source >> >> * Interpret the Core AST within Haskell >> > >> > Interestingly, the first implementation of GHCi was a Core interpreter, >> but >> > it ran into a lot of problems. For starters it would have unsafeCoerce >> > everywhere. Support for unboxed values is very very difficult. >> >> What year is that implementation from? I wouldn't mind taking a look >> for it in the GHC repo history. >> >> > I think around here is a good place to start looking: > https://phabricator.haskell.org/rGHCbca9dd54c2b39638cb4638aaccf6015a104a1df5#021fe2a9 > > Cheers > Simon > > >> >> * is not tagless, so we preserve type info >> > >> > Not sure what you mean here. Your interpreter would be running on top >> of >> > the same RTS with the same data representation, so it would have to use >> the >> > same tagging and representation conventions as the rest of GHC >> >> That's true, if a value comes from a compiled RTS function with a >> polymorphic type then I don't know what its real type is to marshal it >> properly. Drat. >> >> >> * allows top-level names to be redefined >> > >> > This you could do with the extisting byte-code interpreter, by instead >> of >> > linking Names directly you link to some runtime Name-lookup function. >> You >> > would probably want to revert all CAFs when the code changes too; this >> is >> > currently not implemented for byte code. >> >> Right, I considered this but without the type information it's going >> to blow up if I change the arity of a function or a data type or >> whatever. >> >> >> * when a function is applied, it checks the type of its arguments >> > >> > Aha, but what if the arguments come from compiled code? GHC doesn't >> carry >> > type information around at runtime, except that it is possible >> reconstruct >> > types in a limited kind of way (this is what the GHC debugger does). >> >> Indeed, from compiled code e.g. id then id (undefined :: Foo) would >> come back as something unidentifiable as being of type Foo. That's the >> flaw in my plan. >> >> Looks like the current interpreter would have to be extended to >> support this or a whole new one re-implementing all the primitives like >> in GHCJS. >> >> Thanks! >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jun 28 20:02:11 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 28 Jun 2016 20:02:11 +0000 Subject: Msys2 64: progress Message-ID: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> Friends I want to thank everyone who has responded - very helpful! Thanks to your help I am making progress * I re-installed msys64 from scratch, this time following the instructions on the GHC wiki rather than the msys2 page. By doing update-core; then pacman -Su; then pacman -Su again, I got a clean install. Very good! Getting a shell between each step is tricky. o The first shell is gotten with mingw64.bat o After update-core, that file is gone; you have to use msys2_shell.cmd I think o After pacman -Su we get mingw64.exe, which we can use thereafter. * My slow-start problem appears to have gone away. I adopted the fix from you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. I am not absolutely certain that was the problem, but things seem ok now. I also excluded c:/msys64 from my antivirus check. * Emacs too is now working normally. Hurrah So that's all good. Now I'm stuck on the windows tarballs download thing. I get configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz I tried both the things described on the wiki: Pacman -R mingw-w64-x86_64-curl error: target not found: mingw-w64-x86_64-curl For the other I did the two mkdir things, and tried ./configure again, but got the same error message as above. So I'm stuck again, but further forward. Can you advise me? Thanks! Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Jun 28 21:19:11 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Tue, 28 Jun 2016 22:19:11 +0100 Subject: Msys2 64: progress In-Reply-To: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> Hi Simon, You’re missing an underscore in the command (there’s one between x86 and 64), It’s pacman -R mingw-w64-x86_64-curl This is only needed if curl --version reports anything other than x86_64-pc-msys. After that you need to install the normal msys curl with pacman -S curl You don’t have to run configure everytime to test either, you can just run mk/get-win32-tarballs.sh download x86_64 from the root and it should just download the packages only if everything is setup correctly. Also don’t forget to do a pacman -Sy to update the repositories. Couldn’t gather from your email if you did this already. Kind Regards, Tamar From: Simon Peyton Jones via ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jun 28 21:13:28 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 28 Jun 2016 21:13:28 +0000 Subject: Msys2 64: progress In-Reply-To: <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> Message-ID: Actually I had the command right; copy/paste somehow removed the underscore. And curl –version does report curl --version curl 7.49.1 (x86_64-pc-msys) so it should not be necessary anyway. But ./configure still fails with checking for path to top of build tree... C:/code/HEAD configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz Meanwhile mk/get-win32-tarballs.sh download x86_64 completes after 1 second, with no messages of any kind. What next?! Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of lonetiger at gmail.com Sent: 28 June 2016 22:19 To: Simon Peyton Jones via ghc-devs ; David Macek ; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, You’re missing an underscore in the command (there’s one between x86 and 64), It’s pacman -R mingw-w64-x86_64-curl This is only needed if curl --version reports anything other than x86_64-pc-msys. After that you need to install the normal msys curl with pacman -S curl You don’t have to run configure everytime to test either, you can just run mk/get-win32-tarballs.sh download x86_64 from the root and it should just download the packages only if everything is setup correctly. Also don’t forget to do a pacman -Sy to update the repositories. Couldn’t gather from your email if you did this already. Kind Regards, Tamar From: Simon Peyton Jones via ghc-devs Sent: Tuesday, June 28, 2016 21:02 To: David Macek; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: Msys2 64: progress Friends I want to thank everyone who has responded – very helpful! Thanks to your help I am making progress · I re-installed msys64 from scratch, this time following the instructions on the GHC wiki rather than the msys2 page. By doing update-core; then pacman -Su; then pacman -Su again, I got a clean install. Very good! Getting a shell between each step is tricky. o The first shell is gotten with mingw64.bat o After update-core, that file is gone; you have to use msys2_shell.cmd I think o After pacman -Su we get mingw64.exe, which we can use thereafter. · My slow-start problem appears to have gone away. I adopted the fix from you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. I am not absolutely certain that was the problem, but things seem ok now. I also excluded c:/msys64 from my antivirus check. · Emacs too is now working normally. Hurrah So that’s all good. Now I’m stuck on the windows tarballs download thing. I get configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz I tried both the things described on the wiki: Pacman -R mingw-w64-x86_64-curl error: target not found: mingw-w64-x86_64-curl For the other I did the two mkdir things, and tried ./configure again, but got the same error message as above. So I’m stuck again, but further forward. Can you advise me? Thanks! Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Tue Jun 28 22:27:02 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Tue, 28 Jun 2016 22:27:02 +0000 Subject: Msys2 64: progress In-Reply-To: References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> Message-ID: <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> Hi Simon, I’m not sure what’s going on there. I updated my curl to 7.49.1 and I am experiencing the same silent death (--version doesn’t even work for me then which is weird). In any case, downgrading back to 7.48.0 worked for me. I don’t know how to do that with pacman, so instead maybe try: pacman -S wget wget -qO - http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 wget -qO - http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 If it doesn’t work, to upgrade again to 7.49.1 you can just do pacman -S curl libcurl Kind Regards, Tamar From: Simon Peyton Jones -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Tue Jun 28 22:29:20 2016 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 28 Jun 2016 15:29:20 -0700 Subject: Using the GHC API to write an interpreter In-Reply-To: References: Message-ID: On Tue, Jun 28, 2016 at 12:15 PM, Christopher Done wrote: > Thanks! It's strange to think there was once no GHCi. This is an interesting > piece of Haskell implementation history! =) It was really exciting when ghci showed up. No need to separately load everything into hugs! From simonpj at microsoft.com Wed Jun 29 10:18:02 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 29 Jun 2016 10:18:02 +0000 Subject: Msys2 64: progress In-Reply-To: <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> Message-ID: It’s bizarre that pacman won’t let us downgrade curl! I don’t know how to do that with pacman, so instead maybe try: pacman -S wget wget -qO - http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 wget -qO - http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 I tried this. All three commands succeeded, the latter two with no output at all. But once more “./configure” fails with the same message “File not found - *.tar.xz”. It is a bizarre message isn’t it? A lot of files are there: /c/code/HEAD$ ls ghc-tarballs/mingw-w64/ x86_64 /c/code/HEAD$ ls ghc-tarballs/mingw-w64/x86_64/ mingw-w64-x86_64-binutils-2.25.1-1-any.pkg.tar.xz mingw-w64-x86_64-crt-git-5.0.0.4531.49c7046-1-any.pkg.tar.xz mingw-w64-x86_64-gcc-5.2.0-3-any.pkg.tar.xz mingw-w64-x86_64-gcc-libs-5.2.0-3-any.pkg.tar.xz mingw-w64-x86_64-gmp-6.0.0-3-any.pkg.tar.xz mingw-w64-x86_64-headers-git-5.0.0.4531.49c7046-1-any.pkg.tar.xz mingw-w64-x86_64-isl-0.14.1-2-any.pkg.tar.xz mingw-w64-x86_64-libiconv-1.14-5-any.pkg.tar.xz mingw-w64-x86_64-libwinpthread-git-5.0.0.4538.78dca70-1-any.pkg.tar.xz mingw-w64-x86_64-mpc-1.0.3-2-any.pkg.tar.xz mingw-w64-x86_64-mpfr-3.1.3.p0-2-any.pkg.tar.xz mingw-w64-x86_64-winpthreads-git-5.0.0.4538.78dca70-1-any.pkg.tar.xz mingw-w64-x86_64-zlib-1.2.8-8-any.pkg.tar.xz /c/code/HEAD$ ls ghc-tarballs/perl/ ghc-perl-1.tar.gz All I need is for ‘configure’ to get on and un-tar them! Maybe the problem isn’t with curl at all? Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 28 June 2016 23:27 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I’m not sure what’s going on there. I updated my curl to 7.49.1 and I am experiencing the same silent death (--version doesn’t even work for me then which is weird). In any case, downgrading back to 7.48.0 worked for me. I don’t know how to do that with pacman, so instead maybe try: pacman -S wget wget -qO - http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 wget -qO - http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 If it doesn’t work, to upgrade again to 7.49.1 you can just do pacman -S curl libcurl Kind Regards, Tamar From: Simon Peyton Jones Sent: Tuesday, June 28, 2016 21:13 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Actually I had the command right; copy/paste somehow removed the underscore. And curl –version does report curl --version curl 7.49.1 (x86_64-pc-msys) so it should not be necessary anyway. But ./configure still fails with checking for path to top of build tree... C:/code/HEAD configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz Meanwhile mk/get-win32-tarballs.sh download x86_64 completes after 1 second, with no messages of any kind. What next?! Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of lonetiger at gmail.com Sent: 28 June 2016 22:19 To: Simon Peyton Jones via ghc-devs >; David Macek >; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, You’re missing an underscore in the command (there’s one between x86 and 64), It’s pacman -R mingw-w64-x86_64-curl This is only needed if curl --version reports anything other than x86_64-pc-msys. After that you need to install the normal msys curl with pacman -S curl You don’t have to run configure everytime to test either, you can just run mk/get-win32-tarballs.sh download x86_64 from the root and it should just download the packages only if everything is setup correctly. Also don’t forget to do a pacman -Sy to update the repositories. Couldn’t gather from your email if you did this already. Kind Regards, Tamar From: Simon Peyton Jones via ghc-devs Sent: Tuesday, June 28, 2016 21:02 To: David Macek; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: Msys2 64: progress Friends I want to thank everyone who has responded – very helpful! Thanks to your help I am making progress · I re-installed msys64 from scratch, this time following the instructions on the GHC wiki rather than the msys2 page. By doing update-core; then pacman -Su; then pacman -Su again, I got a clean install. Very good! Getting a shell between each step is tricky. o The first shell is gotten with mingw64.bat o After update-core, that file is gone; you have to use msys2_shell.cmd I think o After pacman -Su we get mingw64.exe, which we can use thereafter. · My slow-start problem appears to have gone away. I adopted the fix from you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. I am not absolutely certain that was the problem, but things seem ok now. I also excluded c:/msys64 from my antivirus check. · Emacs too is now working normally. Hurrah So that’s all good. Now I’m stuck on the windows tarballs download thing. I get configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz I tried both the things described on the wiki: Pacman -R mingw-w64-x86_64-curl error: target not found: mingw-w64-x86_64-curl For the other I did the two mkdir things, and tried ./configure again, but got the same error message as above. So I’m stuck again, but further forward. Can you advise me? Thanks! Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Wed Jun 29 10:35:16 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Wed, 29 Jun 2016 10:35:16 +0000 Subject: Msys2 64: progress In-Reply-To: References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> Message-ID: <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> Hi Simon, I think you’re right, That pattern in the error is the one we pass to find find "${base_dir}" -name "*.tar.xz" -exec tar xfJ {} \; on line 334 of configure.ac which is supposed to unpack the files. That the download script doesn’t output nothing makes sense now since the hashes of the files match. I *think* what’s going on here is that for some reason you don’t have findutils installed and it’s instead using The windows “find” utility, which generates that error. C:\Users\Tamar>find *.tar.xz File not found - *.tar.xz Try re-installing findutils, pacman -S findutils, and if find –version doesn’t return the findutils one check your PATH settings. Cheers, Tamar From: Simon Peyton Jones -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 29 11:08:21 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 29 Jun 2016 11:08:21 +0000 Subject: Msys2 64: progress In-Reply-To: <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> Message-ID: Aha! That sounds very plausible. I’ll try. Maybe it’s a path-ordering thing. It would be very cool if ‘configure’ checked that ‘find’ was the find it was expecting, not Windows find. Dunno how to do that, but that check would have saved us a lot of time. (For most other utils, weget, curl etc, there is no Windows program with the same name. But for ‘find’, there is.) Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 29 June 2016 11:35 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I think you’re right, That pattern in the error is the one we pass to find find "${base_dir}" -name "*.tar.xz" -exec tar xfJ {} \; on line 334 of configure.ac which is supposed to unpack the files. That the download script doesn’t output nothing makes sense now since the hashes of the files match. I *think* what’s going on here is that for some reason you don’t have findutils installed and it’s instead using The windows “find” utility, which generates that error. C:\Users\Tamar>find *.tar.xz File not found - *.tar.xz Try re-installing findutils, pacman -S findutils, and if find –version doesn’t return the findutils one check your PATH settings. Cheers, Tamar From: Simon Peyton Jones Sent: Wednesday, June 29, 2016 10:18 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress It’s bizarre that pacman won’t let us downgrade curl! I don’t know how to do that with pacman, so instead maybe try: pacman -S wget wget -qO - http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 wget -qO - http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 I tried this. All three commands succeeded, the latter two with no output at all. But once more “./configure” fails with the same message “File not found - *.tar.xz”. It is a bizarre message isn’t it? A lot of files are there: /c/code/HEAD$ ls ghc-tarballs/mingw-w64/ x86_64 /c/code/HEAD$ ls ghc-tarballs/mingw-w64/x86_64/ mingw-w64-x86_64-binutils-2.25.1-1-any.pkg.tar.xz mingw-w64-x86_64-crt-git-5.0.0.4531.49c7046-1-any.pkg.tar.xz mingw-w64-x86_64-gcc-5.2.0-3-any.pkg.tar.xz mingw-w64-x86_64-gcc-libs-5.2.0-3-any.pkg.tar.xz mingw-w64-x86_64-gmp-6.0.0-3-any.pkg.tar.xz mingw-w64-x86_64-headers-git-5.0.0.4531.49c7046-1-any.pkg.tar.xz mingw-w64-x86_64-isl-0.14.1-2-any.pkg.tar.xz mingw-w64-x86_64-libiconv-1.14-5-any.pkg.tar.xz mingw-w64-x86_64-libwinpthread-git-5.0.0.4538.78dca70-1-any.pkg.tar.xz mingw-w64-x86_64-mpc-1.0.3-2-any.pkg.tar.xz mingw-w64-x86_64-mpfr-3.1.3.p0-2-any.pkg.tar.xz mingw-w64-x86_64-winpthreads-git-5.0.0.4538.78dca70-1-any.pkg.tar.xz mingw-w64-x86_64-zlib-1.2.8-8-any.pkg.tar.xz /c/code/HEAD$ ls ghc-tarballs/perl/ ghc-perl-1.tar.gz All I need is for ‘configure’ to get on and un-tar them! Maybe the problem isn’t with curl at all? Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 28 June 2016 23:27 To: Simon Peyton Jones > Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I’m not sure what’s going on there. I updated my curl to 7.49.1 and I am experiencing the same silent death (--version doesn’t even work for me then which is weird). In any case, downgrading back to 7.48.0 worked for me. I don’t know how to do that with pacman, so instead maybe try: pacman -S wget wget -qO - http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 wget -qO - http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz | tar xJ -C /usr --strip-components=1 If it doesn’t work, to upgrade again to 7.49.1 you can just do pacman -S curl libcurl Kind Regards, Tamar From: Simon Peyton Jones Sent: Tuesday, June 28, 2016 21:13 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Actually I had the command right; copy/paste somehow removed the underscore. And curl –version does report curl --version curl 7.49.1 (x86_64-pc-msys) so it should not be necessary anyway. But ./configure still fails with checking for path to top of build tree... C:/code/HEAD configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz Meanwhile mk/get-win32-tarballs.sh download x86_64 completes after 1 second, with no messages of any kind. What next?! Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of lonetiger at gmail.com Sent: 28 June 2016 22:19 To: Simon Peyton Jones via ghc-devs >; David Macek >; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, You’re missing an underscore in the command (there’s one between x86 and 64), It’s pacman -R mingw-w64-x86_64-curl This is only needed if curl --version reports anything other than x86_64-pc-msys. After that you need to install the normal msys curl with pacman -S curl You don’t have to run configure everytime to test either, you can just run mk/get-win32-tarballs.sh download x86_64 from the root and it should just download the packages only if everything is setup correctly. Also don’t forget to do a pacman -Sy to update the repositories. Couldn’t gather from your email if you did this already. Kind Regards, Tamar From: Simon Peyton Jones via ghc-devs Sent: Tuesday, June 28, 2016 21:02 To: David Macek; tamar at zhox.com Cc: ghc-devs at haskell.org Subject: Msys2 64: progress Friends I want to thank everyone who has responded – very helpful! Thanks to your help I am making progress · I re-installed msys64 from scratch, this time following the instructions on the GHC wiki rather than the msys2 page. By doing update-core; then pacman -Su; then pacman -Su again, I got a clean install. Very good! Getting a shell between each step is tricky. o The first shell is gotten with mingw64.bat o After update-core, that file is gone; you have to use msys2_shell.cmd I think o After pacman -Su we get mingw64.exe, which we can use thereafter. · My slow-start problem appears to have gone away. I adopted the fix from you may be hitting a long standing issue some computers have in which the domain controller is being hit for every invocation of commands, causing a slowdown https://github.com/Alexpux/MSYS2-packages/issues/138 , Solution 2 from https://gist.github.com/k-takata/9b8d143f0f3fef5abdab seems to fix it for most people. I am not absolutely certain that was the problem, but things seem ok now. I also excluded c:/msys64 from my antivirus check. · Emacs too is now working normally. Hurrah So that’s all good. Now I’m stuck on the windows tarballs download thing. I get configure: Checking for Windows toolchain tarballs... configure: Extracting Windows toolchain from archives (may take a while)... File not found - *.tar.xz I tried both the things described on the wiki: Pacman -R mingw-w64-x86_64-curl error: target not found: mingw-w64-x86_64-curl For the other I did the two mkdir things, and tried ./configure again, but got the same error message as above. So I’m stuck again, but further forward. Can you advise me? Thanks! Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Wed Jun 29 11:16:50 2016 From: david.macek.0 at gmail.com (David Macek) Date: Wed, 29 Jun 2016 13:16:50 +0200 Subject: Msys2 64: progress In-Reply-To: <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> Message-ID: On 29. 6. 2016 0:27, lonetiger at gmail.com wrote: > In any case, downgrading back to 7.48.0 worked for me. > > I don’t know how to do that with pacman curl -Os http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz curl -Os http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz pacman -U libcurl-7.48.0-1-x86_64.pkg.tar.xz curl-7.48.0-1-x86_64.pkg.tar.xz rm libcurl-7.48.0-1-x86_64.pkg.tar.xz curl-7.48.0-1-x86_64.pkg.tar.xz -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From david.macek.0 at gmail.com Wed Jun 29 11:21:12 2016 From: david.macek.0 at gmail.com (David Macek) Date: Wed, 29 Jun 2016 13:21:12 +0200 Subject: Msys2 64: progress In-Reply-To: References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> Message-ID: <079662d1-1077-9b9e-4ef2-eeb269c5aab7@gmail.com> On 29. 6. 2016 13:16, David Macek wrote: > On 29. 6. 2016 0:27, lonetiger at gmail.com wrote: >> In any case, downgrading back to 7.48.0 worked for me. >> >> I don’t know how to do that with pacman > > curl -Os http://repo.msys2.org/msys/x86_64/libcurl-7.48.0-1-x86_64.pkg.tar.xz > curl -Os http://repo.msys2.org/msys/x86_64/curl-7.48.0-1-x86_64.pkg.tar.xz > pacman -U libcurl-7.48.0-1-x86_64.pkg.tar.xz curl-7.48.0-1-x86_64.pkg.tar.xz > rm libcurl-7.48.0-1-x86_64.pkg.tar.xz curl-7.48.0-1-x86_64.pkg.tar.xz Oops. If curl doesn't work, substitute with wget as per Tamar's advice, but `pacman -U` is still the right way to install stand-alone package files. -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From ezyang at mit.edu Wed Jun 29 14:34:23 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Wed, 29 Jun 2016 10:34:23 -0400 Subject: Template Haskell determinism In-Reply-To: References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> <1465146843-sup-5444@sabre> Message-ID: <1467210765-sup-5977@sabre> No, nameBase is not the right thing to use here; you also need the unit ID (in GHC 8.0 parlance; package key in GHC 7.10; package id in GHC 7.8 and before). If you have that information, then GHC establishes an invariant that if two names compare stably equal, then the uniques associated with them are the same. Edward Excerpts from Michael Sloan's message of 2016-06-10 17:16:44 -0400: > Hey, sorry for not getting back to this sooner! > > Perhaps I should have added the following to my list of goals in contention: > > (3) (==) shouldn't yield True for Names that have different unique ids. > > We can only have stable comparisons if goal (3) isn't met, and two > different unique Names would be considered to be equivalent based on the > nameBase. This is because Ord is a total order, not a partial order. As > described in my prior email, PartialOrd could be added, but it'd be > inconvenient to use with existing Ord based containers. > > -Michael > > On Sun, Jun 5, 2016 at 10:15 AM, Edward Z. Yang wrote: > > > I must admit, I am a bit confused by this discussion. > > > > It is true that every Name is associated with a Unique. But you don't > > need the Unique to equality/ordering tests; the names also contain > > enough (stable) information for stable comparisons of that sort. So > > why don't we expose that instead of the Unique? > > > > Edward > > > > Excerpts from Michael Sloan's message of 2016-06-04 18:44:03 -0700: > > > On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones < > > simonpj at microsoft.com> > > > wrote: > > > > > > > If names get different ordering keys when reified from different > > modules > > > > (seems like they'd have to, particularly given ghc's "-j"), then we > > end up > > > > with an unpleasant circumstance where these do not compare as equal > > > > > > > > > > > > > > > > The I believe that global, top level names (NameG) are not subject to > > this > > > > ordering stuff, so I don’t think this problem can occur. > > > > > > > > > > True, top level names are NameG. The reified Info for a top level Dec > > may > > > include NameU, though. For example, the type variables in 'Maybe' are > > > NameU: > > > > > > $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe > > > lift (show nf)) > > > > > > The resulting expression is something like "NameU 822083586" > > > > > > > This is a breaking change and it doesn't fix the problem that > > NameFlavour > > > > is > > > > > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > > > > > > > > > But why is NameU exposed to clients? GHC needs to know, but clients > > > > don’t. What use are these packages making of it? > > > > > > > > > > It's being leaked in the public inteface via Ord. The Eq instance is > > fine, > > > because these are Uniques, so the results should be consistent. > > > > > > There are two goals in contention here: > > > > > > 1) Having some ordering on Names so that they can be used in Map or Set > > > 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to > > > really handle these well. In that case, the ordering would be based on > > > everything but the NameU int, but 'Eq' would still follow it > > > > > > A few ideas for different approaches to resolving this: > > > > > > 1) Document it. Less appealing than fixing it in the API, but still > > would > > > be good. > > > > > > 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' > > > newtype (partial ord on the non-unique info), or 'UnstableNameOrd' > > newtype > > > (current behavior). A trickyness of this approach is that you'd need > > > containers that can handle (PartialOrd k, Eq k) keys. In lots of cases > > > people are using the 'Ord' instance with 'Name's that are not 'NameU', so > > > this would break a lot of code that was already deterministic. > > > > > > 3) Some approaches like this ordering key, but I'm not sure how it will > > > help when comparing NameUs from different modules? > > > > > > > S > > > > > > > > > > > > > > > > > > > > > > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of > > *Michael > > > > Sloan > > > > *Sent:* 02 June 2016 02:07 > > > > *To:* Bartosz Nitka > > > > *Cc:* ghc-devs Devs > > > > *Subject:* Re: Template Haskell determinism > > > > > > > > > > > > > > > > +1 to solving this. Not sure about the approach, but assuming the > > > > following concerns are addressed, I'm (+1) on it too: > > > > > > > > > > > > > > > > This solution is clever! However, I think there is some difficulty to > > > > determining this ordering key. Namely, what happens when I construct > > the > > > > (Set Name) using results from multiple reifies? > > > > > > > > > > > > > > > > One solution is to have the ordering key be a consecutive supply that's > > > > initialized on a per-module basis. There is still an issue there, > > though, > > > > which is that you might store one of these names in a global IORef > > that's > > > > used by a later TH splice. Or, similarly, serialize the names to a > > file > > > > and later load them. At least in those cases you need to use 'runIO' > > to > > > > break determinism. > > > > > > > > > > > > > > > > If names get different ordering keys when reified from different > > modules > > > > (seems like they'd have to, particularly given ghc's "-j"), then we > > end up > > > > with an unpleasant circumstance where these do not compare as equal. > > How > > > > about having the Eq instance ignore the ordering key? I think that > > mostly > > > > resolves this concern. This implies that the Ord instance should also > > > > yield EQ and ignore the ordering key, when the unique key matches. > > > > > > > > > > > > > > > > One issue with this is that switching the order of reify could > > > > unexpectedly vary the behavior. > > > > > > > > > > > > > > > > Does the map in TcGblEnv imply that a reify from a later module will > > get > > > > the same ordering key? So does this mean that the keys used in a given > > > > reify depend on which things have already been reified? In that case, > > then > > > > this is also an issue with your solution. Now, it's not a big problem > > at > > > > all, just surprising to the user. > > > > > > > > > > > > > > > > > > > > > > > > If the internal API for Name does change, may as well address > > > > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's > > > > suggested solution of having both the traditional package identifier > > and > > > > package keys in 'Name'. > > > > > > > > > > > > > > > > -Michael > > > > > > > > > > > > > > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka > > wrote: > > > > > > > > Template Haskell with its ability to do arbitrary IO is > > non-deterministic > > > > by > > > > > > > > design. You could for example embed the current date in a file. There > > is > > > > > > > > however one kind of non-deterministic behavior that you can trigger > > > > > > > > accidentally. It has to do with how Names are reified. If you take a > > look > > > > at > > > > > > > > the definition of reifyName you can see that it puts the assigned > > Unique > > > > in a > > > > > > > > NameU: > > > > > > > > > > > > > > > > reifyName :: NamedThing n => n -> TH.Name > > > > > > > > reifyName thing > > > > > > > > | isExternalName name = mk_varg pkg_str mod_str occ_str > > > > > > > > | otherwise = TH.mkNameU occ_str (getKey (getUnique > > name)) > > > > > > > > ... > > > > > > > > NameFlavour which NameU is a constructor of has a default Ord instance, > > > > meaning > > > > > > > > that it ends up comparing the Uniques. The relative ordering of > > Uniques is > > > > not > > > > > > > > guaranteed to be stable across recompilations [1], so this can lead to > > > > > > > > ABI-incompatible binaries. > > > > > > > > > > > > > > > > This isn't an abstract problem and it actually happens in practice. The > > > > > > > > microlens package keeps Names in a Set and later turns that set into a > > > > list. > > > > > > > > The results have different orders of TyVars resulting in different ABI > > > > hashes > > > > > > > > and can potentially be optimized differently. > > > > > > > > > > > > > > > > I believe it's worth to handle this case in a deterministic way and I > > have > > > > a > > > > > > > > solution in mind. The idea is to extend NameU (and potentially NameL) > > with > > > > an > > > > > > > > ordering key. To be more concrete: > > > > > > > > > > > > > > > > - | NameU !Int > > > > > > > > + | NameU !Int !Int > > > > > > > > > > > > > > > > This way the Ord instance can use a stable key and the problem reduces > > to > > > > > > > > ensuring the keys are stable. To generate stable keys we can use the > > fact > > > > that > > > > > > > > reify traverses the expressions in the same order every time and > > > > sequentially > > > > > > > > allocate new keys based on traversal order. The way I have it > > implemented > > > > now > > > > > > > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: > > > > > > > > > > > > > > > > + tcg_th_names :: TcRef (UniqFM Int, Int), > > > > > > > > > > > > > > > > Then the reifyName and qNewName do the necessary bookkeeping and > > translate > > > > the > > > > > > > > Uniques on the fly. > > > > > > > > > > > > > > > > This is a breaking change and it doesn't fix the problem that > > NameFlavour > > > > is > > > > > > > > not abstract and leaks the Uniques. It would break at least: > > > > > > > > > > > > > > > > - singletons > > > > > > > > - th-lift > > > > > > > > - haskell-src-meta > > > > > > > > - shakespeare > > > > > > > > - distributed-closure > > > > > > > > > > > > > > > > I'd like to get feedback if this is an acceptable solution and if the > > > > problem > > > > > > > > is worth solving. > > > > > > > > > > > > > > > > Cheers, > > > > > > > > Bartosz > > > > > > > > > > > > > > > > [1] > > > > > > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques > > > > > > > > > > > > _______________________________________________ > > > > ghc-devs mailing list > > > > ghc-devs at haskell.org > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > < > > https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c1a4a84c9341546403e1508d38a8246ee%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=mjEDuk%2fuRsDLg0q63zaIBeh5e2IyfKnKjcEcRLDvERE%3d > > > > > > > > > > > > > > > > > From mgsloan at gmail.com Wed Jun 29 17:41:13 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 29 Jun 2016 10:41:13 -0700 Subject: Template Haskell determinism In-Reply-To: <1467210765-sup-5977@sabre> References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> <1465146843-sup-5444@sabre> <1467210765-sup-5977@sabre> Message-ID: No, NameU and NameL both lack package key / package id. -Michael On Wed, Jun 29, 2016 at 7:34 AM, Edward Z. Yang wrote: > No, nameBase is not the right thing to use here; you also need the > unit ID (in GHC 8.0 parlance; package key in GHC 7.10; package id > in GHC 7.8 and before). If you have that information, then > GHC establishes an invariant that if two names compare stably equal, > then the uniques associated with them are the same. > > Edward > > Excerpts from Michael Sloan's message of 2016-06-10 17:16:44 -0400: >> Hey, sorry for not getting back to this sooner! >> >> Perhaps I should have added the following to my list of goals in contention: >> >> (3) (==) shouldn't yield True for Names that have different unique ids. >> >> We can only have stable comparisons if goal (3) isn't met, and two >> different unique Names would be considered to be equivalent based on the >> nameBase. This is because Ord is a total order, not a partial order. As >> described in my prior email, PartialOrd could be added, but it'd be >> inconvenient to use with existing Ord based containers. >> >> -Michael >> >> On Sun, Jun 5, 2016 at 10:15 AM, Edward Z. Yang wrote: >> >> > I must admit, I am a bit confused by this discussion. >> > >> > It is true that every Name is associated with a Unique. But you don't >> > need the Unique to equality/ordering tests; the names also contain >> > enough (stable) information for stable comparisons of that sort. So >> > why don't we expose that instead of the Unique? >> > >> > Edward >> > >> > Excerpts from Michael Sloan's message of 2016-06-04 18:44:03 -0700: >> > > On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones < >> > simonpj at microsoft.com> >> > > wrote: >> > > >> > > > If names get different ordering keys when reified from different >> > modules >> > > > (seems like they'd have to, particularly given ghc's "-j"), then we >> > end up >> > > > with an unpleasant circumstance where these do not compare as equal >> > > > >> > > > >> > > > >> > > > The I believe that global, top level names (NameG) are not subject to >> > this >> > > > ordering stuff, so I don’t think this problem can occur. >> > > > >> > > >> > > True, top level names are NameG. The reified Info for a top level Dec >> > may >> > > include NameU, though. For example, the type variables in 'Maybe' are >> > > NameU: >> > > >> > > $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe >> > > lift (show nf)) >> > > >> > > The resulting expression is something like "NameU 822083586" >> > > >> > > > This is a breaking change and it doesn't fix the problem that >> > NameFlavour >> > > > is >> > > > >> > > > not abstract and leaks the Uniques. It would break at least: >> > > > >> > > > >> > > > >> > > > But why is NameU exposed to clients? GHC needs to know, but clients >> > > > don’t. What use are these packages making of it? >> > > > >> > > >> > > It's being leaked in the public inteface via Ord. The Eq instance is >> > fine, >> > > because these are Uniques, so the results should be consistent. >> > > >> > > There are two goals in contention here: >> > > >> > > 1) Having some ordering on Names so that they can be used in Map or Set >> > > 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to >> > > really handle these well. In that case, the ordering would be based on >> > > everything but the NameU int, but 'Eq' would still follow it >> > > >> > > A few ideas for different approaches to resolving this: >> > > >> > > 1) Document it. Less appealing than fixing it in the API, but still >> > would >> > > be good. >> > > >> > > 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' >> > > newtype (partial ord on the non-unique info), or 'UnstableNameOrd' >> > newtype >> > > (current behavior). A trickyness of this approach is that you'd need >> > > containers that can handle (PartialOrd k, Eq k) keys. In lots of cases >> > > people are using the 'Ord' instance with 'Name's that are not 'NameU', so >> > > this would break a lot of code that was already deterministic. >> > > >> > > 3) Some approaches like this ordering key, but I'm not sure how it will >> > > help when comparing NameUs from different modules? >> > > >> > > > S >> > > > >> > > > >> > > > >> > > > >> > > > >> > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of >> > *Michael >> > > > Sloan >> > > > *Sent:* 02 June 2016 02:07 >> > > > *To:* Bartosz Nitka >> > > > *Cc:* ghc-devs Devs >> > > > *Subject:* Re: Template Haskell determinism >> > > > >> > > > >> > > > >> > > > +1 to solving this. Not sure about the approach, but assuming the >> > > > following concerns are addressed, I'm (+1) on it too: >> > > > >> > > > >> > > > >> > > > This solution is clever! However, I think there is some difficulty to >> > > > determining this ordering key. Namely, what happens when I construct >> > the >> > > > (Set Name) using results from multiple reifies? >> > > > >> > > > >> > > > >> > > > One solution is to have the ordering key be a consecutive supply that's >> > > > initialized on a per-module basis. There is still an issue there, >> > though, >> > > > which is that you might store one of these names in a global IORef >> > that's >> > > > used by a later TH splice. Or, similarly, serialize the names to a >> > file >> > > > and later load them. At least in those cases you need to use 'runIO' >> > to >> > > > break determinism. >> > > > >> > > > >> > > > >> > > > If names get different ordering keys when reified from different >> > modules >> > > > (seems like they'd have to, particularly given ghc's "-j"), then we >> > end up >> > > > with an unpleasant circumstance where these do not compare as equal. >> > How >> > > > about having the Eq instance ignore the ordering key? I think that >> > mostly >> > > > resolves this concern. This implies that the Ord instance should also >> > > > yield EQ and ignore the ordering key, when the unique key matches. >> > > > >> > > > >> > > > >> > > > One issue with this is that switching the order of reify could >> > > > unexpectedly vary the behavior. >> > > > >> > > > >> > > > >> > > > Does the map in TcGblEnv imply that a reify from a later module will >> > get >> > > > the same ordering key? So does this mean that the keys used in a given >> > > > reify depend on which things have already been reified? In that case, >> > then >> > > > this is also an issue with your solution. Now, it's not a big problem >> > at >> > > > all, just surprising to the user. >> > > > >> > > > >> > > > >> > > > >> > > > >> > > > If the internal API for Name does change, may as well address >> > > > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's >> > > > suggested solution of having both the traditional package identifier >> > and >> > > > package keys in 'Name'. >> > > > >> > > > >> > > > >> > > > -Michael >> > > > >> > > > >> > > > >> > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka >> > wrote: >> > > > >> > > > Template Haskell with its ability to do arbitrary IO is >> > non-deterministic >> > > > by >> > > > >> > > > design. You could for example embed the current date in a file. There >> > is >> > > > >> > > > however one kind of non-deterministic behavior that you can trigger >> > > > >> > > > accidentally. It has to do with how Names are reified. If you take a >> > look >> > > > at >> > > > >> > > > the definition of reifyName you can see that it puts the assigned >> > Unique >> > > > in a >> > > > >> > > > NameU: >> > > > >> > > > >> > > > >> > > > reifyName :: NamedThing n => n -> TH.Name >> > > > >> > > > reifyName thing >> > > > >> > > > | isExternalName name = mk_varg pkg_str mod_str occ_str >> > > > >> > > > | otherwise = TH.mkNameU occ_str (getKey (getUnique >> > name)) >> > > > >> > > > ... >> > > > >> > > > NameFlavour which NameU is a constructor of has a default Ord instance, >> > > > meaning >> > > > >> > > > that it ends up comparing the Uniques. The relative ordering of >> > Uniques is >> > > > not >> > > > >> > > > guaranteed to be stable across recompilations [1], so this can lead to >> > > > >> > > > ABI-incompatible binaries. >> > > > >> > > > >> > > > >> > > > This isn't an abstract problem and it actually happens in practice. The >> > > > >> > > > microlens package keeps Names in a Set and later turns that set into a >> > > > list. >> > > > >> > > > The results have different orders of TyVars resulting in different ABI >> > > > hashes >> > > > >> > > > and can potentially be optimized differently. >> > > > >> > > > >> > > > >> > > > I believe it's worth to handle this case in a deterministic way and I >> > have >> > > > a >> > > > >> > > > solution in mind. The idea is to extend NameU (and potentially NameL) >> > with >> > > > an >> > > > >> > > > ordering key. To be more concrete: >> > > > >> > > > >> > > > >> > > > - | NameU !Int >> > > > >> > > > + | NameU !Int !Int >> > > > >> > > > >> > > > >> > > > This way the Ord instance can use a stable key and the problem reduces >> > to >> > > > >> > > > ensuring the keys are stable. To generate stable keys we can use the >> > fact >> > > > that >> > > > >> > > > reify traverses the expressions in the same order every time and >> > > > sequentially >> > > > >> > > > allocate new keys based on traversal order. The way I have it >> > implemented >> > > > now >> > > > >> > > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: >> > > > >> > > > >> > > > >> > > > + tcg_th_names :: TcRef (UniqFM Int, Int), >> > > > >> > > > >> > > > >> > > > Then the reifyName and qNewName do the necessary bookkeeping and >> > translate >> > > > the >> > > > >> > > > Uniques on the fly. >> > > > >> > > > >> > > > >> > > > This is a breaking change and it doesn't fix the problem that >> > NameFlavour >> > > > is >> > > > >> > > > not abstract and leaks the Uniques. It would break at least: >> > > > >> > > > >> > > > >> > > > - singletons >> > > > >> > > > - th-lift >> > > > >> > > > - haskell-src-meta >> > > > >> > > > - shakespeare >> > > > >> > > > - distributed-closure >> > > > >> > > > >> > > > >> > > > I'd like to get feedback if this is an acceptable solution and if the >> > > > problem >> > > > >> > > > is worth solving. >> > > > >> > > > >> > > > >> > > > Cheers, >> > > > >> > > > Bartosz >> > > > >> > > > >> > > > >> > > > [1] >> > > > >> > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques >> > > > >> > > > >> > > > _______________________________________________ >> > > > ghc-devs mailing list >> > > > ghc-devs at haskell.org >> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > > < >> > https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c1a4a84c9341546403e1508d38a8246ee%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=mjEDuk%2fuRsDLg0q63zaIBeh5e2IyfKnKjcEcRLDvERE%3d >> > > >> > > > >> > > > >> > > > >> > From mgsloan at gmail.com Wed Jun 29 18:46:48 2016 From: mgsloan at gmail.com (Michael Sloan) Date: Wed, 29 Jun 2016 11:46:48 -0700 Subject: Template Haskell determinism In-Reply-To: References: <7bcbd252616e476b8736549f67f65ade@DB4PR30MB030.064d.mgd.msft.net> <1465146843-sup-5444@sabre> <1467210765-sup-5977@sabre> Message-ID: Also, revisiting this issue, I don't think it is worth solving, just worth documenting. Why? Because TH already lets you do lots of incorrect things. TH already allows you to shoot yourself in the foot all over the place, and that's ok. I'd much rather it be a dangerous power tool than a weak safe tool. When writing TH, you are writing something that's part of the compiler, and the code can often resemble the sort of involved in the middle bits of a compiler. For the cases where stable Ord on Name matters even for local names, you're definitely writing something that's a fairly fancy, nearly compiler-like transformation. Concerns like the stability of Names should be handled by the TH user. -Michael On Wed, Jun 29, 2016 at 10:41 AM, Michael Sloan wrote: > No, NameU and NameL both lack package key / package id. > > -Michael > > On Wed, Jun 29, 2016 at 7:34 AM, Edward Z. Yang wrote: >> No, nameBase is not the right thing to use here; you also need the >> unit ID (in GHC 8.0 parlance; package key in GHC 7.10; package id >> in GHC 7.8 and before). If you have that information, then >> GHC establishes an invariant that if two names compare stably equal, >> then the uniques associated with them are the same. >> >> Edward >> >> Excerpts from Michael Sloan's message of 2016-06-10 17:16:44 -0400: >>> Hey, sorry for not getting back to this sooner! >>> >>> Perhaps I should have added the following to my list of goals in contention: >>> >>> (3) (==) shouldn't yield True for Names that have different unique ids. >>> >>> We can only have stable comparisons if goal (3) isn't met, and two >>> different unique Names would be considered to be equivalent based on the >>> nameBase. This is because Ord is a total order, not a partial order. As >>> described in my prior email, PartialOrd could be added, but it'd be >>> inconvenient to use with existing Ord based containers. >>> >>> -Michael >>> >>> On Sun, Jun 5, 2016 at 10:15 AM, Edward Z. Yang wrote: >>> >>> > I must admit, I am a bit confused by this discussion. >>> > >>> > It is true that every Name is associated with a Unique. But you don't >>> > need the Unique to equality/ordering tests; the names also contain >>> > enough (stable) information for stable comparisons of that sort. So >>> > why don't we expose that instead of the Unique? >>> > >>> > Edward >>> > >>> > Excerpts from Michael Sloan's message of 2016-06-04 18:44:03 -0700: >>> > > On Thu, Jun 2, 2016 at 4:12 AM, Simon Peyton Jones < >>> > simonpj at microsoft.com> >>> > > wrote: >>> > > >>> > > > If names get different ordering keys when reified from different >>> > modules >>> > > > (seems like they'd have to, particularly given ghc's "-j"), then we >>> > end up >>> > > > with an unpleasant circumstance where these do not compare as equal >>> > > > >>> > > > >>> > > > >>> > > > The I believe that global, top level names (NameG) are not subject to >>> > this >>> > > > ordering stuff, so I don’t think this problem can occur. >>> > > > >>> > > >>> > > True, top level names are NameG. The reified Info for a top level Dec >>> > may >>> > > include NameU, though. For example, the type variables in 'Maybe' are >>> > > NameU: >>> > > >>> > > $(do TyConI (DataD _ _ [KindedTV (Name _ nf) _] _ _ _) <- reify ''Maybe >>> > > lift (show nf)) >>> > > >>> > > The resulting expression is something like "NameU 822083586" >>> > > >>> > > > This is a breaking change and it doesn't fix the problem that >>> > NameFlavour >>> > > > is >>> > > > >>> > > > not abstract and leaks the Uniques. It would break at least: >>> > > > >>> > > > >>> > > > >>> > > > But why is NameU exposed to clients? GHC needs to know, but clients >>> > > > don’t. What use are these packages making of it? >>> > > > >>> > > >>> > > It's being leaked in the public inteface via Ord. The Eq instance is >>> > fine, >>> > > because these are Uniques, so the results should be consistent. >>> > > >>> > > There are two goals in contention here: >>> > > >>> > > 1) Having some ordering on Names so that they can be used in Map or Set >>> > > 2) Having law-abiding Eq / Ord instances. We'd need a 'PartialOrd' to >>> > > really handle these well. In that case, the ordering would be based on >>> > > everything but the NameU int, but 'Eq' would still follow it >>> > > >>> > > A few ideas for different approaches to resolving this: >>> > > >>> > > 1) Document it. Less appealing than fixing it in the API, but still >>> > would >>> > > be good. >>> > > >>> > > 2) Remove the 'Ord' instance, and force the user to pick 'NamePartialOrd' >>> > > newtype (partial ord on the non-unique info), or 'UnstableNameOrd' >>> > newtype >>> > > (current behavior). A trickyness of this approach is that you'd need >>> > > containers that can handle (PartialOrd k, Eq k) keys. In lots of cases >>> > > people are using the 'Ord' instance with 'Name's that are not 'NameU', so >>> > > this would break a lot of code that was already deterministic. >>> > > >>> > > 3) Some approaches like this ordering key, but I'm not sure how it will >>> > > help when comparing NameUs from different modules? >>> > > >>> > > > S >>> > > > >>> > > > >>> > > > >>> > > > >>> > > > >>> > > > *From:* ghc-devs [mailto:ghc-devs-bounces at haskell.org] *On Behalf Of >>> > *Michael >>> > > > Sloan >>> > > > *Sent:* 02 June 2016 02:07 >>> > > > *To:* Bartosz Nitka >>> > > > *Cc:* ghc-devs Devs >>> > > > *Subject:* Re: Template Haskell determinism >>> > > > >>> > > > >>> > > > >>> > > > +1 to solving this. Not sure about the approach, but assuming the >>> > > > following concerns are addressed, I'm (+1) on it too: >>> > > > >>> > > > >>> > > > >>> > > > This solution is clever! However, I think there is some difficulty to >>> > > > determining this ordering key. Namely, what happens when I construct >>> > the >>> > > > (Set Name) using results from multiple reifies? >>> > > > >>> > > > >>> > > > >>> > > > One solution is to have the ordering key be a consecutive supply that's >>> > > > initialized on a per-module basis. There is still an issue there, >>> > though, >>> > > > which is that you might store one of these names in a global IORef >>> > that's >>> > > > used by a later TH splice. Or, similarly, serialize the names to a >>> > file >>> > > > and later load them. At least in those cases you need to use 'runIO' >>> > to >>> > > > break determinism. >>> > > > >>> > > > >>> > > > >>> > > > If names get different ordering keys when reified from different >>> > modules >>> > > > (seems like they'd have to, particularly given ghc's "-j"), then we >>> > end up >>> > > > with an unpleasant circumstance where these do not compare as equal. >>> > How >>> > > > about having the Eq instance ignore the ordering key? I think that >>> > mostly >>> > > > resolves this concern. This implies that the Ord instance should also >>> > > > yield EQ and ignore the ordering key, when the unique key matches. >>> > > > >>> > > > >>> > > > >>> > > > One issue with this is that switching the order of reify could >>> > > > unexpectedly vary the behavior. >>> > > > >>> > > > >>> > > > >>> > > > Does the map in TcGblEnv imply that a reify from a later module will >>> > get >>> > > > the same ordering key? So does this mean that the keys used in a given >>> > > > reify depend on which things have already been reified? In that case, >>> > then >>> > > > this is also an issue with your solution. Now, it's not a big problem >>> > at >>> > > > all, just surprising to the user. >>> > > > >>> > > > >>> > > > >>> > > > >>> > > > >>> > > > If the internal API for Name does change, may as well address >>> > > > https://ghc.haskell.org/trac/ghc/ticket/10311 too. I agree with SPJ's >>> > > > suggested solution of having both the traditional package identifier >>> > and >>> > > > package keys in 'Name'. >>> > > > >>> > > > >>> > > > >>> > > > -Michael >>> > > > >>> > > > >>> > > > >>> > > > On Tue, May 31, 2016 at 6:54 AM, Bartosz Nitka >>> > wrote: >>> > > > >>> > > > Template Haskell with its ability to do arbitrary IO is >>> > non-deterministic >>> > > > by >>> > > > >>> > > > design. You could for example embed the current date in a file. There >>> > is >>> > > > >>> > > > however one kind of non-deterministic behavior that you can trigger >>> > > > >>> > > > accidentally. It has to do with how Names are reified. If you take a >>> > look >>> > > > at >>> > > > >>> > > > the definition of reifyName you can see that it puts the assigned >>> > Unique >>> > > > in a >>> > > > >>> > > > NameU: >>> > > > >>> > > > >>> > > > >>> > > > reifyName :: NamedThing n => n -> TH.Name >>> > > > >>> > > > reifyName thing >>> > > > >>> > > > | isExternalName name = mk_varg pkg_str mod_str occ_str >>> > > > >>> > > > | otherwise = TH.mkNameU occ_str (getKey (getUnique >>> > name)) >>> > > > >>> > > > ... >>> > > > >>> > > > NameFlavour which NameU is a constructor of has a default Ord instance, >>> > > > meaning >>> > > > >>> > > > that it ends up comparing the Uniques. The relative ordering of >>> > Uniques is >>> > > > not >>> > > > >>> > > > guaranteed to be stable across recompilations [1], so this can lead to >>> > > > >>> > > > ABI-incompatible binaries. >>> > > > >>> > > > >>> > > > >>> > > > This isn't an abstract problem and it actually happens in practice. The >>> > > > >>> > > > microlens package keeps Names in a Set and later turns that set into a >>> > > > list. >>> > > > >>> > > > The results have different orders of TyVars resulting in different ABI >>> > > > hashes >>> > > > >>> > > > and can potentially be optimized differently. >>> > > > >>> > > > >>> > > > >>> > > > I believe it's worth to handle this case in a deterministic way and I >>> > have >>> > > > a >>> > > > >>> > > > solution in mind. The idea is to extend NameU (and potentially NameL) >>> > with >>> > > > an >>> > > > >>> > > > ordering key. To be more concrete: >>> > > > >>> > > > >>> > > > >>> > > > - | NameU !Int >>> > > > >>> > > > + | NameU !Int !Int >>> > > > >>> > > > >>> > > > >>> > > > This way the Ord instance can use a stable key and the problem reduces >>> > to >>> > > > >>> > > > ensuring the keys are stable. To generate stable keys we can use the >>> > fact >>> > > > that >>> > > > >>> > > > reify traverses the expressions in the same order every time and >>> > > > sequentially >>> > > > >>> > > > allocate new keys based on traversal order. The way I have it >>> > implemented >>> > > > now >>> > > > >>> > > > is to add a new field in TcGblEnv which maps Uniques to allocated keys: >>> > > > >>> > > > >>> > > > >>> > > > + tcg_th_names :: TcRef (UniqFM Int, Int), >>> > > > >>> > > > >>> > > > >>> > > > Then the reifyName and qNewName do the necessary bookkeeping and >>> > translate >>> > > > the >>> > > > >>> > > > Uniques on the fly. >>> > > > >>> > > > >>> > > > >>> > > > This is a breaking change and it doesn't fix the problem that >>> > NameFlavour >>> > > > is >>> > > > >>> > > > not abstract and leaks the Uniques. It would break at least: >>> > > > >>> > > > >>> > > > >>> > > > - singletons >>> > > > >>> > > > - th-lift >>> > > > >>> > > > - haskell-src-meta >>> > > > >>> > > > - shakespeare >>> > > > >>> > > > - distributed-closure >>> > > > >>> > > > >>> > > > >>> > > > I'd like to get feedback if this is an acceptable solution and if the >>> > > > problem >>> > > > >>> > > > is worth solving. >>> > > > >>> > > > >>> > > > >>> > > > Cheers, >>> > > > >>> > > > Bartosz >>> > > > >>> > > > >>> > > > >>> > > > [1] >>> > > > >>> > https://ghc.haskell.org/trac/ghc/wiki/DeterministicBuilds#NondeterministicUniques >>> > > > >>> > > > >>> > > > _______________________________________________ >>> > > > ghc-devs mailing list >>> > > > ghc-devs at haskell.org >>> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> > > > < >>> > https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c1a4a84c9341546403e1508d38a8246ee%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=mjEDuk%2fuRsDLg0q63zaIBeh5e2IyfKnKjcEcRLDvERE%3d >>> > > >>> > > > >>> > > > >>> > > > >>> > From simonpj at microsoft.com Thu Jun 30 07:28:01 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 30 Jun 2016 07:28:01 +0000 Subject: Msys2 64: progress In-Reply-To: References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> Message-ID: <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> Tamar, Luke, David, Andrey, and others OK that was it! Now I can build GHC…. Real progress. But I still can’t validate: sh validate using THREADS=5 make: Entering directory '/c/code/HEAD/utils/checkUniques' ./check-uniques.py ../.. Traceback (most recent call last): File "./check-uniques.py", line 39, in uniques = find_uniques(glob.glob(os.path.join(top_dir, 'compiler', 'prelude', '*.hs'))) File "./check-uniques.py", line 15, in find_uniques ms = unique_re.findall(open(f).read()) File "/usr/lib/python3.4/encodings/ascii.py", line 26, in decode return codecs.ascii_decode(input, self.errors)[0] UnicodeDecodeError: 'ascii' codec can't decode byte 0xe2 in position 15185: ordinal not in range(128) make: *** [Makefile:8: check] Error 1 make: Leaving directory '/c/code/HEAD/utils/checkUniques' /c/code/HEAD$ Any ideas about what might be happening? The Python version is 3.4.3. Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Peyton Jones via ghc-devs Sent: 29 June 2016 12:08 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Aha! That sounds very plausible. I’ll try. Maybe it’s a path-ordering thing. It would be very cool if ‘configure’ checked that ‘find’ was the find it was expecting, not Windows find. Dunno how to do that, but that check would have saved us a lot of time. (For most other utils, weget, curl etc, there is no Windows program with the same name. But for ‘find’, there is.) Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 29 June 2016 11:35 To: Simon Peyton Jones > Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I think you’re right, That pattern in the error is the one we pass to find find "${base_dir}" -name "*.tar.xz" -exec tar xfJ {} \; on line 334 of configure.ac which is supposed to unpack the files. That the download script doesn’t output nothing makes sense now since the hashes of the files match. I *think* what’s going on here is that for some reason you don’t have findutils installed and it’s instead using The windows “find” utility, which generates that error. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lonetiger at gmail.com Thu Jun 30 09:12:14 2016 From: lonetiger at gmail.com (lonetiger at gmail.com) Date: Thu, 30 Jun 2016 10:12:14 +0100 Subject: Msys2 64: progress In-Reply-To: <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> Hi Simon, Could you try with python2 instead? (If it’s installed I think the testsuite would pick it up automatically). Python3 is marked as experimental in the testsuite PYTHON3 = sys.version_info >= (3, 0) if PYTHON3: print("*** WARNING: running testsuite using Python 3.\n" "*** Python 3 support is experimental. See Trac #9184.") And based on that trac, it routinely breaks.. Regards, Tamar From: Simon Peyton Jones -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Thu Jun 30 10:23:17 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 30 Jun 2016 12:23:17 +0200 Subject: Msys2 64: progress In-Reply-To: <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <87a8i3kmay.fsf@smart-cactus.org> Simon Peyton Jones via ghc-devs writes: > Tamar, Luke, David, Andrey, and others > > OK that was it! Now I can build GHC…. Real progress. > > But I still can’t validate: > sh validate > using THREADS=5 > make: Entering directory '/c/code/HEAD/utils/checkUniques' > ./check-uniques.py ../.. > Traceback (most recent call last): > File "./check-uniques.py", line 39, in > uniques = find_uniques(glob.glob(os.path.join(top_dir, 'compiler', 'prelude', '*.hs'))) > File "./check-uniques.py", line 15, in find_uniques > ms = unique_re.findall(open(f).read()) > File "/usr/lib/python3.4/encodings/ascii.py", line 26, in decode > return codecs.ascii_decode(input, self.errors)[0] > UnicodeDecodeError: 'ascii' codec can't decode byte 0xe2 in position 15185: ordinal not in range(128) > make: *** [Makefile:8: check] Error 1 > make: Leaving directory '/c/code/HEAD/utils/checkUniques' > /c/code/HEAD$ > > Any ideas about what might be happening? The Python version is 3.4.3. > I'm not sure why I haven't seen this locally but I think I know what is happening. Could you try D2373 (also available as wip/check-uniques-fix)? Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From simonpj at microsoft.com Thu Jun 30 11:22:07 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 30 Jun 2016 11:22:07 +0000 Subject: Msys2 64: progress In-Reply-To: <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> Message-ID: <7a93e22bd2c84281a56e196ad40a4094@DB4PR30MB030.064d.mgd.msft.net> OK. How do I “try with python2 instead”? SImon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 30 June 2016 10:12 To: Simon Peyton Jones Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, Could you try with python2 instead? (If it’s installed I think the testsuite would pick it up automatically). Python3 is marked as experimental in the testsuite PYTHON3 = sys.version_info >= (3, 0) if PYTHON3: print("*** WARNING: running testsuite using Python 3.\n" "*** Python 3 support is experimental. See Trac #9184.") And based on that trac, it routinely breaks.. Regards, Tamar From: Simon Peyton Jones Sent: Thursday, June 30, 2016 08:28 To: Simon Peyton Jones; lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Tamar, Luke, David, Andrey, and others OK that was it! Now I can build GHC…. Real progress. But I still can’t validate: sh validate using THREADS=5 make: Entering directory '/c/code/HEAD/utils/checkUniques' ./check-uniques.py ../.. Traceback (most recent call last): File "./check-uniques.py", line 39, in uniques = find_uniques(glob.glob(os.path.join(top_dir, 'compiler', 'prelude', '*.hs'))) File "./check-uniques.py", line 15, in find_uniques ms = unique_re.findall(open(f).read()) File "/usr/lib/python3.4/encodings/ascii.py", line 26, in decode return codecs.ascii_decode(input, self.errors)[0] UnicodeDecodeError: 'ascii' codec can't decode byte 0xe2 in position 15185: ordinal not in range(128) make: *** [Makefile:8: check] Error 1 make: Leaving directory '/c/code/HEAD/utils/checkUniques' /c/code/HEAD$ Any ideas about what might be happening? The Python version is 3.4.3. Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Peyton Jones via ghc-devs Sent: 29 June 2016 12:08 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Aha! That sounds very plausible. I’ll try. Maybe it’s a path-ordering thing. It would be very cool if ‘configure’ checked that ‘find’ was the find it was expecting, not Windows find. Dunno how to do that, but that check would have saved us a lot of time. (For most other utils, weget, curl etc, there is no Windows program with the same name. But for ‘find’, there is.) Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 29 June 2016 11:35 To: Simon Peyton Jones > Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I think you’re right, That pattern in the error is the one we pass to find find "${base_dir}" -name "*.tar.xz" -exec tar xfJ {} \; on line 334 of configure.ac which is supposed to unpack the files. That the download script doesn’t output nothing makes sense now since the hashes of the files match. I *think* what’s going on here is that for some reason you don’t have findutils installed and it’s instead using The windows “find” utility, which generates that error. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 30 12:38:11 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 30 Jun 2016 12:38:11 +0000 Subject: Msys2 64: progress In-Reply-To: <7a93e22bd2c84281a56e196ad40a4094@DB4PR30MB030.064d.mgd.msft.net> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> <7a93e22bd2c84281a56e196ad40a4094@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <15190ff21748433f870dc0c4769b177c@DB4PR30MB030.064d.mgd.msft.net> BTW, during ./boot, I get a lot of errors like this. Should I worry? Thanks. Simon Booting . perl: warning: Setting locale failed. perl: warning: Please check that your locale settings: LC_ALL = (unset), LANG = "ENG" are supported and installed on your system. perl: warning: Falling back to the standard locale ("C"). Booting libraries/base/ perl: warning: Setting locale failed. perl: warning: Please check that your locale settings: LC_ALL = (unset), LANG = "ENG" are supported and installed on your system. Booting libraries/directory/ perl: warning: Falling back to the standard locale ("C"). perl: warning: Setting locale failed. perl: warning: Please check that your locale settings: LC_ALL = (unset), LANG = "ENG" are supported and installed on your system. perl: warning: Falling back to the standard locale ("C"). Booting libraries/integer-gmp/ perl: warning: Setting locale failed. perl: warning: Please check that your locale settings: From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Peyton Jones via ghc-devs Sent: 30 June 2016 12:22 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress OK. How do I “try with python2 instead”? SImon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 30 June 2016 10:12 To: Simon Peyton Jones > Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, Could you try with python2 instead? (If it’s installed I think the testsuite would pick it up automatically). Python3 is marked as experimental in the testsuite PYTHON3 = sys.version_info >= (3, 0) if PYTHON3: print("*** WARNING: running testsuite using Python 3.\n" "*** Python 3 support is experimental. See Trac #9184.") And based on that trac, it routinely breaks.. Regards, Tamar From: Simon Peyton Jones Sent: Thursday, June 30, 2016 08:28 To: Simon Peyton Jones; lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Tamar, Luke, David, Andrey, and others OK that was it! Now I can build GHC…. Real progress. But I still can’t validate: sh validate using THREADS=5 make: Entering directory '/c/code/HEAD/utils/checkUniques' ./check-uniques.py ../.. Traceback (most recent call last): File "./check-uniques.py", line 39, in uniques = find_uniques(glob.glob(os.path.join(top_dir, 'compiler', 'prelude', '*.hs'))) File "./check-uniques.py", line 15, in find_uniques ms = unique_re.findall(open(f).read()) File "/usr/lib/python3.4/encodings/ascii.py", line 26, in decode return codecs.ascii_decode(input, self.errors)[0] UnicodeDecodeError: 'ascii' codec can't decode byte 0xe2 in position 15185: ordinal not in range(128) make: *** [Makefile:8: check] Error 1 make: Leaving directory '/c/code/HEAD/utils/checkUniques' /c/code/HEAD$ Any ideas about what might be happening? The Python version is 3.4.3. Thanks Simon From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Simon Peyton Jones via ghc-devs Sent: 29 June 2016 12:08 To: lonetiger at gmail.com Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Aha! That sounds very plausible. I’ll try. Maybe it’s a path-ordering thing. It would be very cool if ‘configure’ checked that ‘find’ was the find it was expecting, not Windows find. Dunno how to do that, but that check would have saved us a lot of time. (For most other utils, weget, curl etc, there is no Windows program with the same name. But for ‘find’, there is.) Simon From: lonetiger at gmail.com [mailto:lonetiger at gmail.com] Sent: 29 June 2016 11:35 To: Simon Peyton Jones > Cc: ghc-devs at haskell.org Subject: RE: Msys2 64: progress Hi Simon, I think you’re right, That pattern in the error is the one we pass to find find "${base_dir}" -name "*.tar.xz" -exec tar xfJ {} \; on line 334 of configure.ac which is supposed to unpack the files. That the download script doesn’t output nothing makes sense now since the hashes of the files match. I *think* what’s going on here is that for some reason you don’t have findutils installed and it’s instead using The windows “find” utility, which generates that error. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.macek.0 at gmail.com Thu Jun 30 12:53:45 2016 From: david.macek.0 at gmail.com (David Macek) Date: Thu, 30 Jun 2016 14:53:45 +0200 Subject: Msys2 64: progress In-Reply-To: <15190ff21748433f870dc0c4769b177c@DB4PR30MB030.064d.mgd.msft.net> References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> <7a93e22bd2c84281a56e196ad40a4094@DB4PR30MB030.064d.mgd.msft.net> <15190ff21748433f870dc0c4769b177c@DB4PR30MB030.064d.mgd.msft.net> Message-ID: On 30. 6. 2016 14:38, Simon Peyton Jones via ghc-devs wrote: > BTW, during ./boot, I get a lot of errors like this. Should I worry? > perl: warning: Setting locale failed. > perl: warning: Please check that your locale settings: > LC_ALL = (unset), > LANG = "ENG" > are supported and installed on your system. > perl: warning: Falling back to the standard locale ("C"). Weird. My MSYS2 autodetects and sets `LANG=en_US.UTF-8`. Can you try setting that in the terminal before running `./boot` and or the testsuite? -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From david.macek.0 at gmail.com Thu Jun 30 12:54:31 2016 From: david.macek.0 at gmail.com (David Macek) Date: Thu, 30 Jun 2016 14:54:31 +0200 Subject: Msys2 64: progress In-Reply-To: References: <211623c64b4d4f7cb1d80e87ae9a84ec@DB4PR30MB030.064d.mgd.msft.net> <5772dbbf.2523c20a.55c3f.08d1@mx.google.com> <5772f9b6.e152c20a.f2c74.32bb@mx.google.com> <5773a464.4ccf1c0a.bc01c.ffffa332@mx.google.com> <9b2d2254b26a4db48e228bc9e8ae67f3@DB4PR30MB030.064d.mgd.msft.net> <5774f07e.83261c0a.f4ff4.14ef@mx.google.com> <7a93e22bd2c84281a56e196ad40a4094@DB4PR30MB030.064d.mgd.msft.net> <15190ff21748433f870dc0c4769b177c@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <0657226d-13f3-1241-b05a-267f9ea7377e@gmail.com> On 30. 6. 2016 14:53, David Macek wrote: > Weird. My MSYS2 autodetects and sets `LANG=en_US.UTF-8`. Can you try setting that in the terminal before running `./boot` and or the testsuite? In bash, that's `export LANG=en_US.UTF-8`. -- David Macek -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 3834 bytes Desc: S/MIME Cryptographic Signature URL: From simonpj at microsoft.com Thu Jun 30 12:55:40 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 30 Jun 2016 12:55:40 +0000 Subject: Trac spam Message-ID: <62a821eaa492436b8b8cfe65d0f24a6c@DB4PR30MB030.064d.mgd.msft.net> If someone could kill this spate of Trac spam, it’d be great. Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Thu Jun 30 17:31:34 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Thu, 30 Jun 2016 13:31:34 -0400 Subject: topHandler03 failing now Message-ID: <1467307599-sup-4349@sabre> Hey thomie, You recently changed topHandler03 to not ignore output. Unfortunately, on my Arch Linux box this causes the test to fail: --- ./topHandler03.run/topHandler03.stderr.normalised 2016-06-30 10:30:56.423442132 -0700 +++ ./topHandler03.run/topHandler03.run.stderr.normalised 2016-06-30 10:30:56.423442132 -0700 @@ -1 +1 @@ -Terminated +/bin/sh: line 1: 7193 Terminated ./topHandler03 It seems the shell output behavior here varies. Edward From ben at well-typed.com Thu Jun 30 17:45:42 2016 From: ben at well-typed.com (Ben Gamari) Date: Thu, 30 Jun 2016 19:45:42 +0200 Subject: Trac Spam Message-ID: <871t3elge1.fsf@smart-cactus.org> Hello everyone, As you may have noticed we were hit with another bout of Trac spam today. I've tightened the spam filter up a bit further and things now seem to be once again under control. Of course, tightening up the spam filter may come at a cost. While I've tried my best to setup the filter such that legitimate uses are unimpeded, filtering is more of an art than a science. Please let me know if you find that you are hasseled with excessive CAPTCHAs or even outright rejection. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: