From ben at well-typed.com Wed Jan 4 05:28:45 2017 From: ben at well-typed.com (Ben Gamari) Date: Wed, 04 Jan 2017 00:28:45 -0500 Subject: [ANNOUNCE] Formation of the initial GHC Steering Committee Message-ID: <87o9zn75rm.fsf@ben-laptop.smart-cactus.org> Dear Haskell community, Over the past months we have discussed changes to GHC's process for collecting, discussing, and considering new language extensions, compiler features, and the like. Happily, we are now ready to move forward with our new proposal process. Towards this end, we have formed the GHC Steering Committee which will be responsible for evaluating the proposals that run through the process. The committee consists of the following members (with GitHub user names given parenthetically), * Chris Allen (@bitemyapp) * Joachim Breitner (@nomeata) * Manuel M T Chakravarty (@mchakravarty) * Iavor Diatchki (@yav) * Atze Dijkstra (@atzedijkstra) * Richard Eisenberg (@goldfirere) * Ben Gamari (@bgamari) * Simon Marlow (@simonmar) * Ryan Newton (@rrnewton) * Simon Peyton-Jones (@simonpj) The body will be chaired jointly by Simon Marlow and Simon Peyton-Jones. Since the ghc-proposals repository was created, it has accumulated nearly thirty pull requests describing a variety of compelling changes. We will consider these proposals to be at the beginning of their four-week discussion period. The goal of this discussion is to find and eliminate weaknesses of the proposal. The final proposal should address all valid points raised in the discussion. When you believe the proposal has converged, bring it to the steering committee and summarize the discussion in a pull request comment. If you would like to contribute a new proposal, please refer to the directions given in the ghc-proposals' repository README [1] and proposal submission guidelines [2]. Cheers, - Ben, on behalf of the GHC Steering Committee [1] https://github.com/ghc-proposals/ghc-proposals [2] https://github.com/ghc-proposals/ghc-proposals/blob/master/proposal-submission.rst -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From simonpj at microsoft.com Wed Jan 4 10:44:59 2017 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 4 Jan 2017 10:44:59 +0000 Subject: GHC rewrite rules for class operations & laws In-Reply-To: <8E34955B-4717-4DD7-AB1C-36DF072B4195@smart-cactus.org> References: <8E34955B-4717-4DD7-AB1C-36DF072B4195@smart-cactus.org> Message-ID: | Indeed, we could eliminate several hundred lines of boilerplate in GHC if we | could lift this restriction. Can you be more specific? Which hundreds of lines? Do add this info to the ticket when Gorge makes it. Or just make one! Simon | -----Original Message----- | From: Ben Gamari [mailto:ben at smart-cactus.org] | Sent: 29 December 2016 14:50 | To: Conal Elliott ; George Colpitts | | Cc: glasgow-haskell-users at haskell.org; Simon Peyton Jones | | Subject: Re: GHC rewrite rules for class operations & laws | | On December 28, 2016 7:27:20 PM EST, Conal Elliott wrote: | >Hi, George. Yes, please do add a task, hopefully to serve as a | >conversation anchor until the issues and path forward are clearer. From | >my perspective, class methods are among the most natural and useful | >candidates for rewrite rules, since they tend to have associated laws, | >many (but not all) of which are helpful in optimization. The | >alternative I know (and am using) is fairly inconvenient: replicating | >entire APIs just in order to delay inlining long enough to apply rules. | > | Indeed, we could eliminate several hundred lines of boilerplate in GHC if we | could lift this restriction. | | Cheers, | | - Ben | From ben at smart-cactus.org Wed Jan 4 14:34:00 2017 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 04 Jan 2017 09:34:00 -0500 Subject: GHC rewrite rules for class operations & laws In-Reply-To: References: <8E34955B-4717-4DD7-AB1C-36DF072B4195@smart-cactus.org> Message-ID: <87tw9eq4h3.fsf@ben-laptop.smart-cactus.org> Welcome back, Simon! Simon Peyton Jones writes: > | Indeed, we could eliminate several hundred lines of boilerplate in GHC if we > | could lift this restriction. > > Can you be more specific? Which hundreds of lines? > In particular the bindings in Data.Int and Data.Word (e.g. GHC.Int.eqInt8, GHC.Word.gtWord64). > Do add this info to the ticket when Gorge makes it. Or just make one! > The ticket is #13044. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From david.feuer at gmail.com Mon Jan 9 02:16:55 2017 From: david.feuer at gmail.com (David Feuer) Date: Sun, 8 Jan 2017 21:16:55 -0500 Subject: Narrower (per-method) GND Message-ID: There are some situations where we may want to use GND to derive some class methods when it's not applicable to others. For example, some people would very much like to add a join method to Monad, but doing so would prevent GND from working for Monad. Similarly, the distribute method of Data.Distributive.Distributive is incompatible with GND. In each of these cases, a perfectly valid, and efficient, way to derive the class would be to use the GND mechanism to derive the methods it works with and the default method definitions for the rest. To cover these cases, I think it would be nice to allow a method declaration to give a default definition intended to be used for GND. This may or may not be the same as the usual default. Some classes can support GND for some methods, but using defaults for the others would give poor implementations. To cover this case, I think it would be nice to add per-method GND-deriving syntax. This could look something like instance C T where deriving f g = .... From mail at joachim-breitner.de Mon Jan 9 04:32:09 2017 From: mail at joachim-breitner.de (Joachim Breitner) Date: Sun, 08 Jan 2017 23:32:09 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: Message-ID: <1483936329.28351.1.camel@joachim-breitner.de> Hi, just responding to this one aspect: Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer: > but using defaults for > the others would give poor implementations. To cover this case, I > think it would be nice to add per-method GND-deriving syntax. This > could look something like > > instance C T where >   deriving f >   g = .... Assuming newtype T = MkT S You can achieve this using instance C T where   f = coerce (f @F)   g = .... (which is precisely what GND does), so I don’t think any new syntax is needed here. 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: 833 bytes Desc: This is a digitally signed message part URL: From david.feuer at gmail.com Mon Jan 9 04:54:35 2017 From: david.feuer at gmail.com (David Feuer) Date: Sun, 8 Jan 2017 23:54:35 -0500 Subject: Narrower (per-method) GND In-Reply-To: <1483936329.28351.1.camel@joachim-breitner.de> References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: You *can* do this, but it's often not so concise. When the type constructor has parameters, you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature for the method type in order to bring into scope variables you then use in the argument to coerce. If you have newtype Foo f a = Foo (Foo f a) then you may need instance Bar f => Bar (Foo f) where bah = coerce (bah @ f @ a) :: forall a . C a => ... to pin down the C instance. If you don't want to use explicit type application (e.g., you're using a library that does not claim to have stable type argument order), things get even more verbose. On Jan 8, 2017 11:32 PM, "Joachim Breitner" wrote: > Hi, > > just responding to this one aspect: > > Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer: > > but using defaults for > > the others would give poor implementations. To cover this case, I > > think it would be nice to add per-method GND-deriving syntax. This > > could look something like > > > > instance C T where > > deriving f > > g = .... > > Assuming > newtype T = MkT S > > You can achieve this using > > instance C T where > f = coerce (f @F) > g = .... > > (which is precisely what GND does), so I don’t think any new syntax is > needed here. > > 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 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at cs.brynmawr.edu Mon Jan 9 18:32:25 2017 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 9 Jan 2017 13:32:25 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables and InstanceSigs. But visible type application should always work, because class methods always have a fixed type argument order. Regardless, requiring users to do all this for GND on Monad would be frustrating. Actually, I just had an insight about this: there is no reason to use one deriving strategy for all methods in an instance. I can think of 4 ways to fill in the implementation of a class method in an instance: 1. Explicit, hand-written implementation 2. Defaulting to the implementation written in the class (or `error "undefined method"` in the absence of a default. This is essentially the default default.) 3. Stock implementation provided by GHC 4. Coerce Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only on newtypes and then imposes role restrictions on the method's type. GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this feature at such a course granularity. What about: > newtype N a = MkN (Foo a) > instance Blah a => C (N a) where > meth1 = ... > deriving default meth2 -- a bit silly really, as you can just leave meth2 out > deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea > deriving newtype meth4 We could also imagine > deriving newtype instance Blah a => Monad (N a) where > deriving default join -- not so silly anymore! This syntax allows a `where` clause on standalone deriving allowing you to override the overall `deriving` behavior on a per-method basis. I actually quite like this extension... Richard > On Jan 8, 2017, at 11:54 PM, David Feuer wrote: > > You *can* do this, but it's often not so concise. When the type constructor has parameters, you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature for the method type in order to bring into scope variables you then use in the argument to coerce. If you have > > newtype Foo f a = Foo (Foo f a) > > then you may need > > instance Bar f => Bar (Foo f) where > bah = coerce (bah @ f @ a) > :: forall a . C a => ... > > to pin down the C instance. > > If you don't want to use explicit type application (e.g., you're using a library that does not claim to have stable type argument order), things get even more verbose. > > On Jan 8, 2017 11:32 PM, "Joachim Breitner" > wrote: > Hi, > > just responding to this one aspect: > > Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer: > > but using defaults for > > the others would give poor implementations. To cover this case, I > > think it would be nice to add per-method GND-deriving syntax. This > > could look something like > > > > instance C T where > > deriving f > > g = .... > > Assuming > newtype T = MkT S > > You can achieve this using > > instance C T where > f = coerce (f @F) > g = .... > > (which is precisely what GND does), so I don’t think any new syntax is > needed here. > > 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 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Mon Jan 9 18:57:55 2017 From: gershomb at gmail.com (Gershom B) Date: Mon, 9 Jan 2017 13:57:55 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: Richard — your idea is really interesting. How would the dreaded role restriction have to be modified to detect and allow this sort of granularity? —g On January 9, 2017 at 1:34:17 PM, Richard Eisenberg (rae at cs.brynmawr.edu) wrote: > I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables > and InstanceSigs. But visible type application should always work, because class methods > always have a fixed type argument order. Regardless, requiring users to do all this for > GND on Monad would be frustrating. > > Actually, I just had an insight about this: there is no reason to use one deriving strategy > for all methods in an instance. I can think of 4 ways to fill in the implementation of a class > method in an instance: > > 1. Explicit, hand-written implementation > 2. Defaulting to the implementation written in the class (or `error "undefined method"` > in the absence of a default. This is essentially the default default.) > 3. Stock implementation provided by GHC > 4. Coerce > > Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due > to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only > on newtypes and then imposes role restrictions on the method's type. > > GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), > or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this > feature at such a course granularity. What about: > > > newtype N a = MkN (Foo a) > > instance Blah a => C (N a) where > > meth1 = ... > > deriving default meth2 -- a bit silly really, as you can just leave meth2 out > > deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea > > deriving newtype meth4 > > We could also imagine > > > deriving newtype instance Blah a => Monad (N a) where > > deriving default join -- not so silly anymore! > > This syntax allows a `where` clause on standalone deriving allowing you to override > the overall `deriving` behavior on a per-method basis. > > I actually quite like this extension... > > Richard > > > > On Jan 8, 2017, at 11:54 PM, David Feuer wrote: > > > > You *can* do this, but it's often not so concise. When the type constructor has parameters, > you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature > for the method type in order to bring into scope variables you then use in the argument > to coerce. If you have > > > > newtype Foo f a = Foo (Foo f a) > > > > then you may need > > > > instance Bar f => Bar (Foo f) where > > bah = coerce (bah @ f @ a) > > :: forall a . C a => ... > > > > to pin down the C instance. > > > > If you don't want to use explicit type application (e.g., you're using a library that > does not claim to have stable type argument order), things get even more verbose. > > > > On Jan 8, 2017 11:32 PM, "Joachim Breitner" > > wrote: > > Hi, > > > > just responding to this one aspect: > > > > Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer: > > > but using defaults for > > > the others would give poor implementations. To cover this case, I > > > think it would be nice to add per-method GND-deriving syntax. This > > > could look something like > > > > > > instance C T where > > > deriving f > > > g = .... > > > > Assuming > > newtype T = MkT S > > > > You can achieve this using > > > > instance C T where > > f = coerce (f @F) > > g = .... > > > > (which is precisely what GND does), so I don’t think any new syntax is > > needed here. > > > > 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 > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From rae at cs.brynmawr.edu Mon Jan 9 19:11:02 2017 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Mon, 9 Jan 2017 14:11:02 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: > On Jan 9, 2017, at 1:57 PM, Gershom B wrote: > > Richard — your idea is really interesting. How would the dreaded role restriction have to be modified to detect and allow this sort of granularity? It wouldn't. The role restriction is purely on a method-by-method basis. (Right now, the role restriction is not enforced at the class level -- you just get a type error on the method that GND produces. See below.) So this new feature wouldn't interact with roles directly, at all. Also, looking back through these emails, I realize my "insight" was really just the logical conclusion of David's original suggestion. Not much of an insight really, just some concrete syntax. Richard Example of bad GND: > class Functor m => M m where > join :: m (m a) -> m a > > newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a } > > instance Functor m => Functor (ReaderT r m) where > fmap f x = ReaderT $ \r -> fmap f (runReaderT x r) > > instance M m => M (ReaderT r m) where > join x = ReaderT $ \r -> join (fmap (($ r) . runReaderT) (runReaderT x r)) > > newtype N m a = MkN (ReaderT Int m a) > deriving (Functor, M) > This produces > • Couldn't match representation of type ‘m (N m a)’ > with that of ‘m (ReaderT Int m a)’ > arising from the coercion of the method ‘join’ > from type ‘forall a. > ReaderT Int m (ReaderT Int m a) -> ReaderT Int m a’ > to type ‘forall a. N m (N m a) -> N m a’ > NB: We cannot know what roles the parameters to ‘m’ have; > we must assume that the role is nominal > • When deriving the instance for (M (N m)) in GHC 8.0.1. > > —g > > > On January 9, 2017 at 1:34:17 PM, Richard Eisenberg (rae at cs.brynmawr.edu) wrote: >> I agree with David that using explicit `coerce`s can be quite verbose and may need ScopedTypeVariables >> and InstanceSigs. But visible type application should always work, because class methods >> always have a fixed type argument order. Regardless, requiring users to do all this for >> GND on Monad would be frustrating. >> >> Actually, I just had an insight about this: there is no reason to use one deriving strategy >> for all methods in an instance. I can think of 4 ways to fill in the implementation of a class >> method in an instance: >> >> 1. Explicit, hand-written implementation >> 2. Defaulting to the implementation written in the class (or `error "undefined method"` >> in the absence of a default. This is essentially the default default.) >> 3. Stock implementation provided by GHC >> 4. Coerce >> >> Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type constraints due >> to a `default` signature. Way 3 restricts the choice of class and type. Way 4 works only >> on newtypes and then imposes role restrictions on the method's type. >> >> GHC provides a `deriving` mechanism so that you can request Way 2 (`default`), 3 (`stock`), >> or 4 (`newtype`) to fill in every method in a class. But there's no need to provide this >> feature at such a course granularity. What about: >> >>> newtype N a = MkN (Foo a) >>> instance Blah a => C (N a) where >>> meth1 = ... >>> deriving default meth2 -- a bit silly really, as you can just leave meth2 out >>> deriving stock meth3 -- also silly, as C isn't a stock class, but you get the idea >>> deriving newtype meth4 >> >> We could also imagine >> >>> deriving newtype instance Blah a => Monad (N a) where >>> deriving default join -- not so silly anymore! >> >> This syntax allows a `where` clause on standalone deriving allowing you to override >> the overall `deriving` behavior on a per-method basis. >> >> I actually quite like this extension... >> >> Richard >> >> >>> On Jan 8, 2017, at 11:54 PM, David Feuer wrote: >>> >>> You *can* do this, but it's often not so concise. When the type constructor has parameters, >> you need to pin them down using ScopedTypeVariables. So you end up needing to give a signature >> for the method type in order to bring into scope variables you then use in the argument >> to coerce. If you have >>> >>> newtype Foo f a = Foo (Foo f a) >>> >>> then you may need >>> >>> instance Bar f => Bar (Foo f) where >>> bah = coerce (bah @ f @ a) >>> :: forall a . C a => ... >>> >>> to pin down the C instance. >>> >>> If you don't want to use explicit type application (e.g., you're using a library that >> does not claim to have stable type argument order), things get even more verbose. >>> >>> On Jan 8, 2017 11:32 PM, "Joachim Breitner" > >> wrote: >>> Hi, >>> >>> just responding to this one aspect: >>> >>> Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer: >>>> but using defaults for >>>> the others would give poor implementations. To cover this case, I >>>> think it would be nice to add per-method GND-deriving syntax. This >>>> could look something like >>>> >>>> instance C T where >>>> deriving f >>>> g = .... >>> >>> Assuming >>> newtype T = MkT S >>> >>> You can achieve this using >>> >>> instance C T where >>> f = coerce (f @F) >>> g = .... >>> >>> (which is precisely what GND does), so I don’t think any new syntax is >>> needed here. >>> >>> 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 >>> _______________________________________________ >>> Glasgow-haskell-users mailing list >>> Glasgow-haskell-users at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> >>> >>> _______________________________________________ >>> Glasgow-haskell-users mailing list >>> Glasgow-haskell-users at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users From david.feuer at gmail.com Mon Jan 9 22:11:31 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 9 Jan 2017 17:11:31 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg wrote: > 2. Defaulting to the implementation written in the class (or `error > "undefined method"` in the absence of a default. This is essentially the > default default.) I want to be able to specify that a certain default definition is good enough not to worry about. For example (with horribly bad syntax), class Applicative m => Monad m where (>>=) :: m a -> (a -> m b) -> m b m >>= f = join (f <$> m) -- plain old default join :: m (m a) -> m a good_enough_default join = (>>= id) This would allow users to just write newtype Foo a = Foo ... deriving Monad which would then be equivalent (using the notation you came up with) to instance Monad Foo where deriving newtype (>>=) David Feuer From david.feuer at gmail.com Mon Jan 9 22:22:56 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 9 Jan 2017 17:22:56 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg wrote: > I agree with David that using explicit `coerce`s can be quite verbose and > may need ScopedTypeVariables and InstanceSigs. But visible type application > should always work, because class methods always have a fixed type argument > order. Oh, I missed this bit. That claim is not quite true. I could have something like class Two f where two :: (Integral a, Num b) => proxy (f a b) -> String Unless the package defining this class promises not to, its maintainer could later change that to two :: forall b a proxy . (Integral a, Num b) => proxy (f a b) -> String which could silently break code. Or change the position of the proxy argument and loudly break code. From ben at well-typed.com Wed Jan 11 18:40:45 2017 From: ben at well-typed.com (Ben Gamari) Date: Wed, 11 Jan 2017 13:40:45 -0500 Subject: [ANNOUNCE] Glasgow Haskell Compiler 8.0.2 is available! Message-ID: <87wpe1ignm.fsf@ben-laptop.smart-cactus.org> =============================================== The Glasgow Haskell Compiler -- version 8.0.2 =============================================== The GHC team is happy to at last announce the 8.0.2 release of the Glasgow Haskell Compiler. Source and binary distributions are available at http://downloads.haskell.org/~ghc/8.0.2/ This is the second release of the 8.0 series and fixes nearly two-hundred bugs. These include, * Interface file build determinism (#4012). * Compatibility with macOS Sierra and GCC compilers which compile position-independent executables by default * Compatibility with systems which use the gold linker * Runtime linker fixes on Windows (see #12797) * A compiler bug which resulted in undefined reference errors while compiling some packages (see #12076) * A number of memory consistency bugs in the runtime system * A number of efficiency issues in the threaded runtime which manifest on larger core counts and large numbers of bound threads. * A typechecker bug which caused some programs using -XDefaultSignatures to be incorrectly accepted. * More than two-hundred other bugs. See Trac [1] for a complete listing. * #12757, which lead to broken runtime behavior and even crashes in the presence of primitive strings. * #12844, a type inference issue affecting partial type signatures. * A bump of the `directory` library, fixing buggy path canonicalization behavior (#12894). Unfortunately this required a major version bump in `directory` and minor bumps in several other libraries. * #12912, where use of the `select` system call would lead to runtime system failures with large numbers of open file handles. * #10635, wherein -Wredundant-constraints was included in the -Wall warning set A more detailed list of the changes included in this release can be found in the release notes, https://downloads.haskell.org/~ghc/8.0.2/docs/html/users_guide/8.0.2-notes.html Please note that this release breaks with our usual tendency to avoid major version bumps of core libraries in minor GHC releases by including an upgrade of the `directory` library to 1.3.0.0. Also note that, due to a rather serious bug (#13100) affecting Windows noticed late in the release cycle, the Windows binary distributions were produced using a slightly patched [2] source tree. Users compiling from source for Windows should be certain to include this patch in their build. This release is the result of six months of effort by the GHC development community. We'd like to thank everyone who has contributed code, bug reports, and feedback to this release. It's only due to their efforts that GHC remains a vibrant and exciting project. [1] https://ghc.haskell.org/trac/ghc/query?status=closed&milestone=8.0.2&col=id&col=summary&col=status&col=type&col=priority&col=milestone&col=component&order=priority [2] http://downloads.haskell.org/~ghc/8.0.2/0001-SysTools-Revert-linker-flags-change.patch How to get it ~~~~~~~~~~~~~ Both the source tarball and binary distributions for a wide variety of platforms are available at, http://www.haskell.org/ghc/ Background ~~~~~~~~~~ Haskell is a standardized lazy functional programming language. The Glasgow Haskell Compiler (GHC) is a state-of-the-art programming suite for Haskell. Included is an optimising compiler generating efficient code for a variety of platforms, together with an interactive system for convenient, quick development. The distribution includes space and time profiling facilities, a large collection of libraries, and support for various language extensions, including concurrency, exceptions, and foreign language interfaces. GHC is distributed under a BSD-style open source license. Supported Platforms ~~~~~~~~~~~~~~~~~~~ The list of platforms we support, and the people responsible for them, can be found on the GHC wiki http://ghc.haskell.org/trac/ghc/wiki/Platforms Ports to other platforms are possible with varying degrees of difficulty. The Building Guide describes how to go about porting to a new platform: http://ghc.haskell.org/trac/ghc/wiki/Building Developers ~~~~~~~~~~ We welcome new contributors. Instructions on getting started with hacking on GHC are available from GHC's developer site, http://ghc.haskell.org/trac/ghc/ Community Resources ~~~~~~~~~~~~~~~~~~~ There are mailing lists for GHC users, develpoers, and monitoring bug tracker activity; to subscribe, use the web interfaces at http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-tickets There are several other Haskell and GHC-related mailing lists on www.haskell.org; for the full list, see https://mail.haskell.org/cgi-bin/mailman/listinfo Some GHC developers hang out on the #ghc and #haskell of the Freenode IRC network, too: http://www.haskell.org/haskellwiki/IRC_channel Please report bugs using our bug tracking system. Instructions on reporting bugs can be found here: http://www.haskell.org/ghc/reportabug -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From ben at well-typed.com Thu Jan 12 06:04:43 2017 From: ben at well-typed.com (Ben Gamari) Date: Thu, 12 Jan 2017 01:04:43 -0500 Subject: [ANNOUNCE] Glasgow Haskell Compiler 8.0.2 is available! In-Reply-To: <87wpe1ignm.fsf@ben-laptop.smart-cactus.org> References: <87wpe1ignm.fsf@ben-laptop.smart-cactus.org> Message-ID: <87ziiwstj8.fsf@ben-laptop.smart-cactus.org> Ben Gamari writes: > =============================================== > The Glasgow Haskell Compiler -- version 8.0.2 > =============================================== > > The GHC team is happy to at last announce the 8.0.2 release of the > Glasgow Haskell Compiler. Source and binary distributions are available > at > I'm sorry to say that the Windows tarballs were built without profiling libraries and will need to be reissued. To prevent confusion I have removed the bad tarballs until I have a chance to rebuild them. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From mle+hs at mega-nerd.com Thu Jan 12 08:46:09 2017 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Thu, 12 Jan 2017 19:46:09 +1100 Subject: Rewrite rules Message-ID: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> HI all, I'm having an look at rewrite rules, but something bugs me a little. How do I tell if my rewrite rules are firing or not? Even If I introduce deliberate errors in the function name that is being re-written I still don't get so much as a warning. Clues? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From michael at snoyman.com Thu Jan 12 08:59:14 2017 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 12 Jan 2017 10:59:14 +0200 Subject: Rewrite rules In-Reply-To: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> References: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> Message-ID: Could be I'm misunderstanding, but are you looking for -ddump-rule-firings? On Thu, Jan 12, 2017 at 10:46 AM, Erik de Castro Lopo wrote: > HI all, > > I'm having an look at rewrite rules, but something bugs me a little. > How do I tell if my rewrite rules are firing or not? Even If I > introduce deliberate errors in the function name that is being > re-written I still don't get so much as a warning. > > Clues? > > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rwbarton at gmail.com Thu Jan 12 13:01:21 2017 From: rwbarton at gmail.com (Reid Barton) Date: Thu, 12 Jan 2017 08:01:21 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: On Mon, Jan 9, 2017 at 5:11 PM, David Feuer wrote: > On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg wrote: > >> 2. Defaulting to the implementation written in the class (or `error >> "undefined method"` in the absence of a default. This is essentially the >> default default.) > > I want to be able to specify that a certain default definition is good > enough not to worry about. Is this the same as the purpose of the MINIMAL pragma? http://ghc.readthedocs.io/en/latest/glasgow_exts.html#minimal-pragma Imagine GND provides implementations for those methods whose types are amenable to `coerce`ion and leaves the other methods without definitions. Then, taking into account the MINIMAL pragma, GHC either does or does not produce a warning/error about missing class methods, maybe customized to mention the failure to `coerce` a method in GND. Would that be adequate? Regards, Reid Barton From david.feuer at gmail.com Thu Jan 12 14:41:47 2017 From: david.feuer at gmail.com (David Feuer) Date: Thu, 12 Jan 2017 09:41:47 -0500 Subject: Narrower (per-method) GND In-Reply-To: References: <1483936329.28351.1.camel@joachim-breitner.de> Message-ID: No, I don't think that would be adequate, but maybe there's a way to work that in. It's inadequate because MINIMAL doesn't carry any assertion of efficiency. If I indicate I want a class derived by GND, and it works, then I expect its implementation to be, at worst, very very slightly slower than the underlying implementation. If the class author doesn't make such a claim, I want users to have to be explicit about the methods derived by GND. On Jan 12, 2017 8:01 AM, "Reid Barton" wrote: > On Mon, Jan 9, 2017 at 5:11 PM, David Feuer wrote: > > On Mon, Jan 9, 2017 at 1:32 PM, Richard Eisenberg > wrote: > > > >> 2. Defaulting to the implementation written in the class (or `error > >> "undefined method"` in the absence of a default. This is essentially the > >> default default.) > > > > I want to be able to specify that a certain default definition is good > > enough not to worry about. > > Is this the same as the purpose of the MINIMAL pragma? > http://ghc.readthedocs.io/en/latest/glasgow_exts.html#minimal-pragma > > Imagine GND provides implementations for those methods whose types are > amenable to `coerce`ion and leaves the other methods without > definitions. Then, taking into account the MINIMAL pragma, GHC either > does or does not produce a warning/error about missing class methods, > maybe customized to mention the failure to `coerce` a method in GND. > Would that be adequate? > > Regards, > Reid Barton > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mle+hs at mega-nerd.com Fri Jan 13 09:27:42 2017 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Fri, 13 Jan 2017 20:27:42 +1100 Subject: Rewrite rules In-Reply-To: References: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> Message-ID: <20170113202742.51afa5e69fa3342c6fb8d7da@mega-nerd.com> Michael Snoyman wrote: > Could be I'm misunderstanding, but are you looking for -ddump-rule-firings? Wasn't aware of that, but my question was a little more general. If I write a library that includes rewrite rules, how can I ensure that they fire in client code that someone else writes? What guarantees (however loose) are there? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From mail at joachim-breitner.de Fri Jan 13 15:00:52 2017 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 13 Jan 2017 10:00:52 -0500 Subject: Rewrite rules In-Reply-To: <20170113202742.51afa5e69fa3342c6fb8d7da@mega-nerd.com> References: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> <20170113202742.51afa5e69fa3342c6fb8d7da@mega-nerd.com> Message-ID: <1484319652.471.6.camel@joachim-breitner.de> Hi, Am Freitag, den 13.01.2017, 20:27 +1100 schrieb Erik de Castro Lopo: > Michael Snoyman wrote: > > > Could be I'm misunderstanding, but are you looking for -ddump-rule- > > firings? > > Wasn't aware of that, but my question was a little more general. > > If I write a library that includes rewrite rules, how can I ensure > that they fire in client code that someone else writes? What > guarantees (however loose) are there? very little. The best one can do right now is to know enough about Core and the inliner to predict when things are going to be inlined and when not, what else can go wrong (wrappers maybe?), add the necessary controls (`NOINLINE [0]` etc.), and then hope for the best. And track down any instances of failed rewriting that you learn about. You might also be able to set up your code so that it fails (at runtime, with error) if the desired rules did not fire. This would be nicer if we had https://ghc.haskell.org/trac/ghc/ticket/9180. You can also ask for review if it is public code. 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: 833 bytes Desc: This is a digitally signed message part URL: From david.feuer at gmail.com Sun Jan 15 19:37:51 2017 From: david.feuer at gmail.com (David Feuer) Date: Sun, 15 Jan 2017 14:37:51 -0500 Subject: Derived Functor instance for void types In-Reply-To: References: Message-ID: Currently, if you write data V a deriving Functor GHC generates fmap _ _ = error "Void fmap" This seems quite unfortunate, because it loses potentially useful error information: fmap (+ 3) (error "Too many snozzcumbers!") throws "Void fmap", rather than the much more precise "Too many snozzcumbers!" I've opened Trac #13117 to fix this, but I figured I should double check that no one is opposed. David Feuer -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Jan 16 04:17:36 2017 From: david.feuer at gmail.com (David Feuer) Date: Sun, 15 Jan 2017 23:17:36 -0500 Subject: Derived Functor instance for void types In-Reply-To: References: Message-ID: I don't know what you mean. fmap for an uninhabited type is vacuously strict: its result is always _|_. On Sun, Jan 15, 2017 at 11:00 PM, Kevin Cotrone wrote: > That seems to have a surprising strictness. > > I'm not sure if it would be the best idea to try and evaluate a type with no > inhabitants. > > On Sun, Jan 15, 2017 at 2:37 PM, David Feuer wrote: >> >> Currently, if you write >> >> data V a deriving Functor >> >> GHC generates >> >> fmap _ _ = error "Void fmap" >> >> This seems quite unfortunate, because it loses potentially useful error >> information: >> >> fmap (+ 3) (error "Too many snozzcumbers!") >> >> throws "Void fmap", rather than the much more precise "Too many >> snozzcumbers!" I've opened Trac #13117 to fix this, but I figured I should >> double check that no one is opposed. >> >> David Feuer >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > From ekmett at gmail.com Mon Jan 16 07:29:43 2017 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 16 Jan 2017 02:29:43 -0500 Subject: Derived Functor instance for void types In-Reply-To: References: Message-ID: "Preserving user bottoms" was found to be better behavior for us with Void as well back in the day. Evaluating such a term to get the bottom out is better than making up one that loses information for the user about precisely what bottom it is they had. We do so with absurd and the like for Void. This way if you map over a structure with errors at the leaves you get a new structure with those same errors at the leaves. *tl;dr* +1 from me. -Edward On Sun, Jan 15, 2017 at 11:00 PM, Kevin Cotrone wrote: > That seems to have a surprising strictness. > > I'm not sure if it would be the best idea to try and evaluate a type with > no inhabitants. > > On Sun, Jan 15, 2017 at 2:37 PM, David Feuer > wrote: > >> Currently, if you write >> >> data V a deriving Functor >> >> GHC generates >> >> fmap _ _ = error "Void fmap" >> >> This seems quite unfortunate, because it loses potentially useful error >> information: >> >> fmap (+ 3) (error "Too many snozzcumbers!") >> >> throws "Void fmap", rather than the much more precise "Too many >> snozzcumbers!" I've opened Trac #13117 to fix this, but I figured I should >> double check that no one is opposed. >> >> David Feuer >> >> _______________________________________________ >> Libraries mailing list >> Libraries at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >> > > _______________________________________________ > Libraries mailing list > Libraries at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mle+hs at mega-nerd.com Mon Jan 16 09:09:13 2017 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Mon, 16 Jan 2017 20:09:13 +1100 Subject: Rewrite rules In-Reply-To: <1484319652.471.6.camel@joachim-breitner.de> References: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> <20170113202742.51afa5e69fa3342c6fb8d7da@mega-nerd.com> <1484319652.471.6.camel@joachim-breitner.de> Message-ID: <20170116200913.f0e4539dd939b6469374a539@mega-nerd.com> Joachim Breitner wrote: > very little. The best one can do right now is to know enough about Core > and the inliner to predict when things are going to be inlined and when > not, what else can go wrong (wrappers maybe?), add the necessary > controls (`NOINLINE [0]` etc.), and then hope for the best. And track > down any instances of failed rewriting that you learn about. > > You might also be able to set up your code so that it fails (at > runtime, with error) if the desired rules did not fire. This would be > nicer if we had https://ghc.haskell.org/trac/ghc/ticket/9180. > > You can also ask for review if it is public code. Ok, I'm heading in this direction and then I figure out that the parser for the rewrite rules doesn't even reject obvious syntax errors. Say I have a data types: data Word128 = Word128 Word64 Word64 and inspired by the `fromIntegral` rules for Word64 I write: {-# RULES "fromIntegral/Word64->Word128" fromIntegral = \w64 -> Word128 0 w64 #-} all is fine and dandy. However if I introduce an obvious syntax error like reversing the `->`: {-# RULES "fromIntegral/Word64<-Word128" fromIntegral = \w64 -> Word128 0 w64 #-} I don't get any warning or anything. I've read the docs for rewrite rules: https://downloads.haskell.org/~ghc/8.0.1/docs/html/users_guide/glasgow_exts.html#rewrite-rules but they are rather sparse and again are very short on guarantees. Have I just managed to find myself a new project? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From david.feuer at gmail.com Mon Jan 16 12:18:27 2017 From: david.feuer at gmail.com (David Feuer) Date: Mon, 16 Jan 2017 07:18:27 -0500 Subject: Rewrite rules In-Reply-To: References: <20170112194609.8e61af368f4cad8701f4b887@mega-nerd.com> <20170113202742.51afa5e69fa3342c6fb8d7da@mega-nerd.com> <1484319652.471.6.camel@joachim-breitner.de> <20170116200913.f0e4539dd939b6469374a539@mega-nerd.com> Message-ID: No. The part in quotes is the *name* of the rewrite rule, which is reported to the user when GHC is called with things like -ddump-rule-rewrites and is otherwise completely ignored. On Jan 16, 2017 4:09 AM, "Erik de Castro Lopo" wrote: Joachim Breitner wrote: > very little. The best one can do right now is to know enough about Core > and the inliner to predict when things are going to be inlined and when > not, what else can go wrong (wrappers maybe?), add the necessary > controls (`NOINLINE [0]` etc.), and then hope for the best. And track > down any instances of failed rewriting that you learn about. > > You might also be able to set up your code so that it fails (at > runtime, with error) if the desired rules did not fire. This would be > nicer if we had https://ghc.haskell.org/trac/ghc/ticket/9180. > > You can also ask for review if it is public code. Ok, I'm heading in this direction and then I figure out that the parser for the rewrite rules doesn't even reject obvious syntax errors. Say I have a data types: data Word128 = Word128 Word64 Word64 and inspired by the `fromIntegral` rules for Word64 I write: {-# RULES "fromIntegral/Word64->Word128" fromIntegral = \w64 -> Word128 0 w64 #-} all is fine and dandy. However if I introduce an obvious syntax error like reversing the `->`: {-# RULES "fromIntegral/Word64<-Word128" fromIntegral = \w64 -> Word128 0 w64 #-} I don't get any warning or anything. I've read the docs for rewrite rules: https://downloads.haskell.org/~ghc/8.0.1/docs/html/users_ guide/glasgow_exts.html#rewrite-rules but they are rather sparse and again are very short on guarantees. Have I just managed to find myself a new project? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users at haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users -------------- next part -------------- An HTML attachment was scrubbed... URL: From juhpetersen at gmail.com Thu Jan 19 00:37:54 2017 From: juhpetersen at gmail.com (Jens Petersen) Date: Thu, 19 Jan 2017 09:37:54 +0900 Subject: [ANNOUNCE] Glasgow Haskell Compiler 8.0.2 is available! In-Reply-To: <87wpe1ignm.fsf@ben-laptop.smart-cactus.org> References: <87wpe1ignm.fsf@ben-laptop.smart-cactus.org> Message-ID: On 12 January 2017 at 03:40, Ben Gamari wrote: > The GHC team is happy to at last announce the 8.0.2 release of the > Glasgow Haskell Compiler. Source and binary distributions are available > Thank you Fedora 24+ and RHEL 7 et al users can install it from my Fedora Copr repo: https://copr.fedorainfracloud.org/coprs/petersen/ghc-8.0.2/ The Fedora builds have been there for some time now but I just added the EPEL7 build yesterday. Jens -------------- next part -------------- An HTML attachment was scrubbed... URL: From jhala at cs.ucsd.edu Wed Jan 25 00:09:04 2017 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Tue, 24 Jan 2017 16:09:04 -0800 Subject: Accessing the "original" names via GHC API Message-ID: Hi, I'm quite vexed trying to do the following. Suppose I have a file: ``` module Foo import qualified Data.Set as S baz :: S.Set Int baz = S.empty ``` My goal is to write a function tyconString :: TyCon -> String (perhaps with extra parameters) such that given the `TyCon` corresponding to `Set`, I get back the "original" name `S.Set`, or even `Data.Set.Set`. Everything I've tried, which is fiddling with different variants of `PprStyle`, end up giving me `Data.Set.Base.Set` Does anyone have a suggestion for how to proceed? Thanks! - Ranjit. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Wed Jan 25 02:11:35 2017 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 24 Jan 2017 21:11:35 -0500 Subject: Accessing the "original" names via GHC API In-Reply-To: References: Message-ID: <1485310295.7475.1.camel@joachim-breitner.de> Hi Ranjit, Am Dienstag, den 24.01.2017, 16:09 -0800 schrieb Ranjit Jhala: > My goal is to write a function > >    tyconString :: TyCon -> String  > > (perhaps with extra parameters) such that given the  > `TyCon` corresponding to `Set`, I get back the "original"  > name `S.Set`, or even `Data.Set.Set`.  > > Everything I've tried, which is fiddling with different variants of > `PprStyle`, end up giving me `Data.Set.Base.Set` > > Does anyone have a suggestion for how to proceed? in a way, `Data.Set.Base.Set` is the “original”, proper name for Set, everything else is just a local view on the name. So, are you maybe looking for a way to get the “most natural way” to print a name in a certain module context? This functionality must exist somewhere, as ghci is printing out errors this way. But it certainly would require an additional argument to tyconString, to specify in which module to print the name. 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: 833 bytes Desc: This is a digitally signed message part URL: From jhala at cs.ucsd.edu Wed Jan 25 03:00:05 2017 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Tue, 24 Jan 2017 19:00:05 -0800 Subject: Accessing the "original" names via GHC API In-Reply-To: <1485310295.7475.1.camel@joachim-breitner.de> References: <1485310295.7475.1.camel@joachim-breitner.de> Message-ID: Dear Joachim, You are right -- some more context. Given tc :: TyCon m :: ModName env :: HscEnv I want to get a s :: String such that _in_ the context given by `m` and `env` I can resolve `s` to get back the original `TyCon`, e.g. something like L _ rn <- hscParseIdentifier env s name <- lookupRdrName env modName rn would then return `name :: Name` which corresponds to the original `TyCon`. That is, the goal is _not_ pretty printing, but "serialization" into a String representation that lets me recover the original `TyCon` later. (Consequently, `"Data.Set.Base.Set"` doesn't work as the `Data.Set.Base` module is hidden and hence, when I try the above, GHC complains that the name is not in scope. Does that clarify the problem? Thanks! - Ranjit. On Tue, Jan 24, 2017 at 6:11 PM, Joachim Breitner wrote: > Hi Ranjit, > > Am Dienstag, den 24.01.2017, 16:09 -0800 schrieb Ranjit Jhala: > > My goal is to write a function > > > > tyconString :: TyCon -> String > > > > (perhaps with extra parameters) such that given the > > `TyCon` corresponding to `Set`, I get back the "original" > > name `S.Set`, or even `Data.Set.Set`. > > > > Everything I've tried, which is fiddling with different variants of > > `PprStyle`, end up giving me `Data.Set.Base.Set` > > > > Does anyone have a suggestion for how to proceed? > > in a way, `Data.Set.Base.Set` is the “original”, proper name for Set, > everything else is just a local view on the name. > > So, are you maybe looking for a way to get the “most natural way” to > print a name in a certain module context? > > This functionality must exist somewhere, as ghci is printing out errors > this way. But it certainly would require an additional argument to > tyconString, to specify in which module to print the name. > > 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 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jan 25 08:46:07 2017 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 25 Jan 2017 08:46:07 +0000 Subject: Accessing the "original" names via GHC API In-Reply-To: References: Message-ID: The TyCon has a Name (use tyConName to get it). The Name has a Module and an OccName (use nameModule and nameOccName to get them) The OccName has a string (occNameString) The Module has a ModuleName and a Package. All of these will give the “original-name” info, ignoring what’s in scope. Does that help? S From: Glasgow-haskell-users [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Ranjit Jhala Sent: 25 January 2017 00:09 To: glasgow-haskell-users at haskell.org Subject: Accessing the "original" names via GHC API Hi, I'm quite vexed trying to do the following. Suppose I have a file: ``` module Foo import qualified Data.Set as S baz :: S.Set Int baz = S.empty ``` My goal is to write a function tyconString :: TyCon -> String (perhaps with extra parameters) such that given the `TyCon` corresponding to `Set`, I get back the "original" name `S.Set`, or even `Data.Set.Set`. Everything I've tried, which is fiddling with different variants of `PprStyle`, end up giving me `Data.Set.Base.Set` Does anyone have a suggestion for how to proceed? Thanks! - Ranjit. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Wed Jan 25 09:00:08 2017 From: ezyang at mit.edu (Edward Z. Yang) Date: Wed, 25 Jan 2017 01:00:08 -0800 Subject: Accessing the "original" names via GHC API In-Reply-To: References: <1485310295.7475.1.camel@joachim-breitner.de> Message-ID: <1485334295-sup-5215@sabre> Hi Ranjit, Unfortunately you need more information to do this, since the set of modules which are available for import can vary depending on whether or not packages are hidden or not (not even counting whether or not a module is exposed or not!) The way GHC's pretty printer gives a good name is that it keeps track of all of the names in scope and where they came from in a GlobalRdrEnv. The relevant code is in 'mkPrintUnqualified' in HscTypes, but if you pretty print using user-style with an appropriately set up GlobalRdrEnv you should get the things you want. Edward Excerpts from Ranjit Jhala's message of 2017-01-24 19:00:05 -0800: > Dear Joachim, > > You are right -- some more context. > > Given > > tc :: TyCon > m :: ModName > env :: HscEnv > > I want to get a > > s :: String > > such that _in_ the context given by `m` and `env` I can resolve `s` to get > back the original `TyCon`, e.g. something like > > L _ rn <- hscParseIdentifier env s > name <- lookupRdrName env modName rn > > would then return `name :: Name` which corresponds to the original `TyCon`. > > That is, the goal is _not_ pretty printing, but "serialization" into a > String > representation that lets me recover the original `TyCon` later. > > (Consequently, `"Data.Set.Base.Set"` doesn't work as the `Data.Set.Base` > module is hidden and hence, when I try the above, GHC complains that the > name is not in scope. > > Does that clarify the problem? > > Thanks! > > - Ranjit. > > > On Tue, Jan 24, 2017 at 6:11 PM, Joachim Breitner > wrote: > > > Hi Ranjit, > > > > Am Dienstag, den 24.01.2017, 16:09 -0800 schrieb Ranjit Jhala: > > > My goal is to write a function > > > > > > tyconString :: TyCon -> String > > > > > > (perhaps with extra parameters) such that given the > > > `TyCon` corresponding to `Set`, I get back the "original" > > > name `S.Set`, or even `Data.Set.Set`. > > > > > > Everything I've tried, which is fiddling with different variants of > > > `PprStyle`, end up giving me `Data.Set.Base.Set` > > > > > > Does anyone have a suggestion for how to proceed? > > > > in a way, `Data.Set.Base.Set` is the “original”, proper name for Set, > > everything else is just a local view on the name. > > > > So, are you maybe looking for a way to get the “most natural way” to > > print a name in a certain module context? > > > > This functionality must exist somewhere, as ghci is printing out errors > > this way. But it certainly would require an additional argument to > > tyconString, to specify in which module to print the name. > > > > 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 > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > From jhala at cs.ucsd.edu Wed Jan 25 14:14:40 2017 From: jhala at cs.ucsd.edu (Ranjit Jhala) Date: Wed, 25 Jan 2017 06:14:40 -0800 Subject: Accessing the "original" names via GHC API In-Reply-To: <1485334295-sup-5215@sabre> References: <1485310295.7475.1.camel@joachim-breitner.de> <1485334295-sup-5215@sabre> Message-ID: @Simon, The route you outline was the one we already use -- but that gives back the full name "Data.Set.Base.Set" (instead of "S.Set" or "Data.Set.Set"), as the module is "Data.Set.Base". @Edward, Yes, I think your suggestion should work! This business of determining which packages/modules are hidden is exactly what we are trying to get around. (In this case, Data.Set.Base is hidden...) Thanks all! - Ranjit. On Wed, Jan 25, 2017 at 1:00 AM, Edward Z. Yang wrote: > Hi Ranjit, > > Unfortunately you need more information to do this, since the > set of modules which are available for import can vary depending > on whether or not packages are hidden or not (not even counting > whether or not a module is exposed or not!) > > The way GHC's pretty printer gives a good name is that it keeps > track of all of the names in scope and where they came from > in a GlobalRdrEnv. The relevant code is in 'mkPrintUnqualified' > in HscTypes, but if you pretty print using user-style with > an appropriately set up GlobalRdrEnv you should > get the things you want. > > Edward > > Excerpts from Ranjit Jhala's message of 2017-01-24 19:00:05 -0800: > > Dear Joachim, > > > > You are right -- some more context. > > > > Given > > > > tc :: TyCon > > m :: ModName > > env :: HscEnv > > > > I want to get a > > > > s :: String > > > > such that _in_ the context given by `m` and `env` I can resolve `s` to > get > > back the original `TyCon`, e.g. something like > > > > L _ rn <- hscParseIdentifier env s > > name <- lookupRdrName env modName rn > > > > would then return `name :: Name` which corresponds to the original > `TyCon`. > > > > That is, the goal is _not_ pretty printing, but "serialization" into a > > String > > representation that lets me recover the original `TyCon` later. > > > > (Consequently, `"Data.Set.Base.Set"` doesn't work as the `Data.Set.Base` > > module is hidden and hence, when I try the above, GHC complains that the > > name is not in scope. > > > > Does that clarify the problem? > > > > Thanks! > > > > - Ranjit. > > > > > > On Tue, Jan 24, 2017 at 6:11 PM, Joachim Breitner < > mail at joachim-breitner.de> > > wrote: > > > > > Hi Ranjit, > > > > > > Am Dienstag, den 24.01.2017, 16:09 -0800 schrieb Ranjit Jhala: > > > > My goal is to write a function > > > > > > > > tyconString :: TyCon -> String > > > > > > > > (perhaps with extra parameters) such that given the > > > > `TyCon` corresponding to `Set`, I get back the "original" > > > > name `S.Set`, or even `Data.Set.Set`. > > > > > > > > Everything I've tried, which is fiddling with different variants of > > > > `PprStyle`, end up giving me `Data.Set.Base.Set` > > > > > > > > Does anyone have a suggestion for how to proceed? > > > > > > in a way, `Data.Set.Base.Set` is the “original”, proper name for Set, > > > everything else is just a local view on the name. > > > > > > So, are you maybe looking for a way to get the “most natural way” to > > > print a name in a certain module context? > > > > > > This functionality must exist somewhere, as ghci is printing out errors > > > this way. But it certainly would require an additional argument to > > > tyconString, to specify in which module to print the name. > > > > > > 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 > > > _______________________________________________ > > > Glasgow-haskell-users mailing list > > > Glasgow-haskell-users at haskell.org > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: