From anthony.d.clayden at gmail.com Thu Jan 6 02:19:31 2022 From: anthony.d.clayden at gmail.com (Anthony Clayden) Date: Thu, 6 Jan 2022 15:19:31 +1300 Subject: Typing of Pattern Synonyms: Required vs Provided constraints Message-ID: There was an interesting exchange between the authors of Haskell compilers back in 1999 (i.e. when there were multiple compilers) http://web.archive.org/web/20151001142647/http://code.haskell.org/~dons/haskell-1990-2000/msg04061.html I was trying to simulate SPJ's point of view, using PatternSynonyms. > > {-# LANGUAGE DatatypeContexts, PatternSynonyms #-} > > data Ord a => TSPJ a = MkTSPJ a a > > pattern PatTSPJ :: (Ord a) => () => a -> a -> TSPJ a -- empty Provided > pattern PatTSPJ x y = MkTSPJ x y > > unPatTSPJ :: TSPJ a -> (a, a) -- no constraints > unPatTSPJ (PatTSPJ x y) = (x, y) > `unPatSPJ`'s binding rejected `No instance for (Ord a) arising from a pattern`. If I don't give a signature, inferred `unPatTSPJ :: Ord b => TSPJ b -> (b, b)`. Taking the DatatypeContext off the `data` decl doesn't make a difference. So Pattern syns seem to be giving exactly the 'stupid theta' behaviour. The User Guide https://downloads.haskell.org/~ghc/8.10.7/docs/html/users_guide/glasgow_exts.html#typing-of-pattern-synonyms says - ⟨CProv⟩ are the constraints *made available (provided)* by a successful pattern match. But it doesn't mean that. It's more like "⟨CProv⟩ are the constraints made available *in addition to ⟨CReq⟩* (provided union required) by a successful pattern match." Or ... is there some way to simulate the up-to-1999 GHC behaviour? (I happen to agree with SPJ; Wadler wasn't thinking it through; consider for example constructor classes over type constructors with constraints: there's nothing in the instance head for the constraint to attach to. Now that we have GADTs -- which are appropriate for a different job -- that DT Contexts perhaps were being (ab-)used for -- I agree more strongly with SPJ.) With GADTs I could get a `unGSPJ` that doesn't expose/provide the constraint, but it does that by packing the constraint/dictionary (polluting) inside the data constructor. Not what I want. As SPJ says down-thread "when you take a constructor *apart*, the invariant must hold by construction: you couldn't have built the thing you are taking apart unless invariant held. So enforcing the invariant again is redundant; and in addition it pollutes the type of selectors." AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Thu Jan 6 20:08:22 2022 From: lists at richarde.dev (Richard Eisenberg) Date: Thu, 6 Jan 2022 20:08:22 +0000 Subject: Typing of Pattern Synonyms: Required vs Provided constraints In-Reply-To: References: Message-ID: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> > On Jan 5, 2022, at 9:19 PM, Anthony Clayden wrote: > > So Pattern syns seem to be giving exactly the 'stupid theta' behaviour. In your example, yes: the Required context is "stupid" in the way that "stupid theta" is. The reason to have a Required context is if your pattern synonym does computation that requires a constraint. For example: pattern Is3 :: (Num a, Eq a) => a -- only a Required constraint pattern Is3 = ((==) 3 -> True) -- that's a view pattern In your case, there is no computation (your pattern synonym just stands for a constructor), so the Required context is unhelpful (and does indeed act just like a datatype context). > > The User Guide https://downloads.haskell.org/~ghc/8.10.7/docs/html/users_guide/glasgow_exts.html#typing-of-pattern-synonyms says > > ⟨CProv⟩ are the constraints made available (provided) by a successful pattern match. > But it doesn't mean that. It's more like "⟨CProv⟩ are the constraints made available *in addition to ⟨CReq⟩* (provided union required) by a successful pattern match." I agree with the user guide here: the Provided constraints are made available. The Required constraint must *already* be available before the pattern match, so they are not made available *by* the match. It is true, though, that in the context of the match, both the Provided and the Required constraints must be satisfiable. To get the pre-1999 behavior, you would need a different type for a pattern synonym used as a pattern than for one used as an expression. This is the subject of the accepted-but-not-implemented https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0042-bidir-constr-sigs.rst Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Thu Jan 6 20:43:04 2022 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Thu, 6 Jan 2022 21:43:04 +0100 Subject: Typing of Pattern Synonyms: Required vs Provided constraints In-Reply-To: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> References: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> Message-ID: Fwiw, a less contrived, and much more relatable, version of Richard's example would be pattern Is3 :: (Num a, Eq a) => a -- only a Required constraint pattern Is3 = 3 -- a polymorphic literal! I think it can be quite instructive for people new to patsyn typing to work out why this is exactly the same as the one in Richard's email! On Thu, Jan 6, 2022, 21:11 Richard Eisenberg wrote: > > > On Jan 5, 2022, at 9:19 PM, Anthony Clayden > wrote: > > So Pattern syns seem to be giving exactly the 'stupid theta' behaviour. > > > In your example, yes: the Required context is "stupid" in the way that > "stupid theta" is. The reason to have a Required context is if your pattern > synonym does computation that requires a constraint. For example: > > pattern Is3 :: (Num a, Eq a) => a -- only a Required constraint > pattern Is3 = ((==) 3 -> True) -- that's a view pattern > > In your case, there is no computation (your pattern synonym just stands > for a constructor), so the Required context is unhelpful (and does indeed > act just like a datatype context). > > > The User Guide > https://downloads.haskell.org/~ghc/8.10.7/docs/html/users_guide/glasgow_exts.html#typing-of-pattern-synonyms > says > > > - ⟨CProv⟩ are the constraints *made available (provided)* by a > successful pattern match. > > But it doesn't mean that. It's more like "⟨CProv⟩ are the constraints > made available *in addition to ⟨CReq⟩* (provided union required) by a > successful pattern match." > > > I agree with the user guide here: the Provided constraints are made > available. The Required constraint must *already* be available before the > pattern match, so they are not made available *by* the match. It is true, > though, that in the context of the match, both the Provided and the > Required constraints must be satisfiable. > > To get the pre-1999 behavior, you would need a different type for a > pattern synonym used as a pattern than for one used as an expression. This > is the subject of the accepted-but-not-implemented > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0042-bidir-constr-sigs.rst > > Richard > > _______________________________________________ > 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 anthony.d.clayden at gmail.com Fri Jan 7 01:10:03 2022 From: anthony.d.clayden at gmail.com (Anthony Clayden) Date: Fri, 7 Jan 2022 14:10:03 +1300 Subject: Fwd: Typing of Pattern Synonyms: Required vs Provided constraints In-Reply-To: References: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> Message-ID: Thanks Gergö, I do find Richard's tendency to use ViewPattern examples distracts me from understanding the point. That arrow-to-nowhere or arrow-to-the-wrong-value syntax is nausea-inducing. Your "instructive" example is really nothing to do with PatSyns, just ordinary Haskell numeric patterns: the Language Report (section 3.17.2 point 7., same wording in 2010 and '98) says a numeric literal in a pattern gets desugared to an `(==)` test against `fromInteger `. So that explains where the constraints come from. (Annoyingly, the you can't express in legit Haskell source.) Avoiding distractions is why my o.p. used an `Ord` constraint, also to follow SPJ's 1999 example. And the canonical example in those old discussions (like Hughes' 1999 paper) is an `Ord` constraint for elements of a `Set` structured as a BST. With your "polymorphic literal" how do I follow the Language Report to desugar? I'd rather be able to write Richard's example using an as-Pattern like one of these: > pattern x at Is3 | x == fromInteger (#3#) = x -- where #3# is the inexpressible > pattern x at 3@Is3 = x (It's not that I'm "new to patsyn typing"; it's more that patsyn typing and design keeps falling short of what I hope from such a promising feature. So I always want to check I'm not mis-understanding. Specifically, the design for Pattern Synonyms was a lost opportunity to expunge ViewPatterns entirely.) AntC On Fri, 7 Jan 2022 at 09:43, Gergő Érdi wrote: > Fwiw, a less contrived, and much more relatable, version of Richard's > example would be > > > pattern Is3 :: (Num a, Eq a) => a -- only a Required constraint > pattern Is3 = 3 -- a polymorphic literal! > > I think it can be quite instructive for people new to patsyn typing to > work out why this is exactly the same as the one in Richard's email! > > > On Thu, Jan 6, 2022, 21:11 Richard Eisenberg wrote: > >> >> >> ... >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony.d.clayden at gmail.com Fri Jan 7 02:00:45 2022 From: anthony.d.clayden at gmail.com (Anthony Clayden) Date: Fri, 7 Jan 2022 15:00:45 +1300 Subject: Typing of Pattern Synonyms: Required vs Provided constraints In-Reply-To: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> References: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> Message-ID: On Fri, 7 Jan 2022 at 09:08, Richard Eisenberg wrote: > > > On Jan 5, 2022, at 9:19 PM, Anthony Clayden > wrote: > > So Pattern syns seem to be giving exactly the 'stupid theta' behaviour. > > > In your example, yes: the Required context is "stupid" in the way that > "stupid theta" is. The reason to have a Required context is if your pattern > synonym does computation that requires a constraint. ... > I don't think that's the only (or even the chief) reason. Wadler's response on that 1999 thread is telling "Often, a type will make no sense without the constraints; e.g., an association list type Alist a b makes no sense unless Eq a holds. The class constraints on data declarations were a simple way for the user to ask the compiler to enforce this invariant. They have compile-time effect only, no effect whatsoever on run-time (in particular, no dictionaries should be passed). " And yet he's somehow forgotten his own design for constraints: the _only_ way to enforce a constraint is by providing evidence in the form of a dictionary. (This is especially impossible for a constructor class where it's the (invisible) argument type to the constructor that wants the constraint.) That's why I agree with SPJ 1999 here: on a pattern match there's no mechanism to pass in a constraint (dictionary-as-evidence); and you're not doing computation in merely matching -- it doesn't even need `Eq`. In a pattern > baz (MkT 3 3) = "Three" -- desugars to > baz (MkT x y) | x == fromInteger #3#, y == fromInteger #3# = "Three" It's the appearance of the `==` and `fromInteger` that Require `(Eq a, Num a)`; I don't expect them Provided by `T`'s nor `MkT`'s Datatype context. And in general, guards can induce arbitrary computation; it's not the responsibility of the datatype declarer to anticipate that. (A Separation of Concerns argument.) So I want constraints 'Required' for building -- that is constraints 'sighted' whether or not any computation involved; but not 'Provided' by matching -- because they're already sighted by the very fact of having built the pattern (to paraphrase SPJ1999). Thanks for pointing out that proposal. I guess it'll achieve what I want for a BST or Wadler's assoc list; would be nice to see an explicit example. I don't want to use a GADT here, because it's the same constraint on every data constructor; and a BST recurses with the same constraint; holding identical dictionaries inside each node is just clutter. Something accessing the BST (probably) needs to bring its `Ord` dictionary with it (`elem` for example); but not necessarily (`count`, `toList` or `show`). > > > The User Guide > https://downloads.haskell.org/~ghc/8.10.7/docs/html/users_guide/glasgow_exts.html#typing-of-pattern-synonyms > says > > > - ⟨CProv⟩ are the constraints *made available (provided)* by a > successful pattern match. > > But it doesn't mean that. It's more like "⟨CProv⟩ are the constraints > made available *in addition to ⟨CReq⟩* (provided union required) by a > successful pattern match." > > > I agree with the user guide here: the Provided constraints are made > available. The Required constraint must *already* be available before the > pattern match, > I disagree. To "be available" requires a dictionary. A pattern synonym gets desugarred, it doesn't hold a dictionary itself. The dictionary *was* "already available" at the time of building; but it's no longer available unless the PatSyn got desugarred to a GADT with that dictionary inside. I want these PatSyns desugarred to ordinary H98 data constructors. And I want an empty Provided `:: (Ord a) => () => a -> a -> T a` to mean nothing is Provided, not even what was Required. > > > To get the pre-1999 behavior, you would need a different type for a > pattern synonym used as a pattern than for one used as an expression. This > is the subject of the accepted-but-not-implemented > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0042-bidir-constr-sigs.rst > > > AntC -------------- next part -------------- An HTML attachment was scrubbed... URL: From anthony.d.clayden at gmail.com Fri Jan 7 03:44:10 2022 From: anthony.d.clayden at gmail.com (Anthony Clayden) Date: Fri, 7 Jan 2022 16:44:10 +1300 Subject: Typing of Pattern Synonyms: Required vs Provided constraints [was cafe DatatypeContexts / alternative] In-Reply-To: References: <010f017e3101b4dc-b55e279d-d037-4805-a8eb-9e5796fa88e7-000000@us-east-2.amazonses.com> Message-ID: [Picking up a cafe thread from February that fits here https://mail.haskell.org/pipermail/haskell-cafe/2021-February/133459.html.] Am 23.02.21 um 20:07 schrieb Richard Eisenberg: >* You might be interested in my recent paper on exactly this problem: *>* how to make DatatypeContexts actually work the way you want: *>* https://richarde.dev/papers/2020/partialdata/partialdata.pdf *>* >.* I think that paper is _not_ how DatatypeContexts should work -- at least for the example in that thread of `fmap` over a data structure wanting to preserve some invariant, such as unique elements. - For the matching/Provided constraints the paper at least does no harm by magically unveiling constraints via a Well-Formed-Type mechanism. It would equally do no harm by just not Providing any constraints at all. - For the building/Required constraints: it would do harm to magically unveil (for example) a computation to squish out duplicates or re-order elements by their `fmap`ed result. The Laws for `Functor.fmap` include "preserving the structure of " the Functor. Squishing out duplicates/reordering/rebalancing breaks that. Instead of `fmap` you should use `Foldable.foldMap :: Monoid m => (a -> m) -> t a -> m`; with `m` instance of the form `Ord b => Monoid (t b)` -- `Ord` induced from the Datatype context of `t`. Then there is a mechanism to pass in the `Ord` dictionary from outside/no need for WFT magic. I get it that Required `Ord b` is a poor stand-in for the invariant: no duplicates; elements in ascending sequence; BST balanced. So the Monoid instance still couldn't expose the underlying data constructors. Forcing to use `foldMap` at least puts it in the programmer's face that trying to use `fmap` is a type error standing in for law-breaking. AntC On Fri, 7 Jan 2022 at 15:00, Anthony Clayden wrote: > > > On Fri, 7 Jan 2022 at 09:08, Richard Eisenberg wrote: > >> >> >> On Jan 5, 2022, at 9:19 PM, Anthony Clayden >> wrote: >> >> So Pattern syns seem to be giving exactly the 'stupid theta' behaviour. >> >> >> In your example, yes: the Required context is "stupid" in the way that >> "stupid theta" is. The reason to have a Required context is if your pattern >> synonym does computation that requires a constraint. ... >> > > I don't think that's the only (or even the chief) reason. Wadler's > response on that 1999 thread is telling > > "Often, a type will make no sense without the constraints; e.g., an > association list type Alist a b makes no sense unless Eq a holds. The > class constraints on data declarations were a simple way for the user to > ask the compiler to enforce this invariant. They have compile-time effect > only, no effect whatsoever on run-time (in particular, no dictionaries > should be passed). " > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From juhpetersen at gmail.com Sun Jan 23 07:30:26 2022 From: juhpetersen at gmail.com (Jens Petersen) Date: Sun, 23 Jan 2022 15:30:26 +0800 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: <20211225202027.jxlafyybul4bltfb@zubin-msi> References: <20211225202027.jxlafyybul4bltfb@zubin-msi> Message-ID: First of all a big thank you and congratulations on the highly anticipated 9.0.2 release. I have been putting off this mail for a while: I actually built it last month right away in Fedora's new ghc9.0 package (available now for all current Fedora releases). Also Stackage Nightly (primarily thanks to Adam Bergmark) was updated to 9.0.2, since nightly-2022-01-10. :-) However two points I wanted to mention: - firstly (minor), the libraries/containers source is not clean (which explains why the tarball is so big) - More serious: why was Win32 major bumped from 2.10 to 2.12? - this breaks foundation, hence current Stackage Nightly is kind of broken for Windows now: https://github.com/commercialhaskell/stackage/issues/6400 I can't really see any good way to resolve this in the short term. Thanks, Jens On Sun, 26 Dec 2021 at 04:23, Zubin Duggal wrote: > The GHC developers are very happy to at long last announce the > availability of GHC 9.0.2. Binary distributions, source distributions, > and documentation are available at the > [usual place](https://downloads.haskell.org/ghc/9.0.2/). > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Sun Jan 23 07:40:05 2022 From: david.feuer at gmail.com (David Feuer) Date: Sun, 23 Jan 2022 02:40:05 -0500 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: References: <20211225202027.jxlafyybul4bltfb@zubin-msi> Message-ID: Could you explain what you mean about the containers source not being "clean"? On Sun, Jan 23, 2022, 2:31 AM Jens Petersen wrote: > First of all a big thank you and congratulations on the highly anticipated > 9.0.2 release. > > I have been putting off this mail for a while: > I actually built it last month right away in Fedora's new ghc9.0 package > (available now for all current Fedora releases). > Also Stackage Nightly (primarily thanks to Adam Bergmark) was updated to > 9.0.2, since nightly-2022-01-10. :-) > > However two points I wanted to mention: > > - firstly (minor), the libraries/containers source is not clean (which > explains why the tarball is so big) > > > - More serious: why was Win32 major bumped from 2.10 to 2.12? > - this breaks foundation, hence current Stackage Nightly is kind of > broken for Windows now: > https://github.com/commercialhaskell/stackage/issues/6400 > > I can't really see any good way to resolve this in the short term. > > Thanks, Jens > > > On Sun, 26 Dec 2021 at 04:23, Zubin Duggal wrote: > >> The GHC developers are very happy to at long last announce the >> availability of GHC 9.0.2. Binary distributions, source distributions, >> and documentation are available at the >> [usual place](https://downloads.haskell.org/ghc/9.0.2/). >> >> _______________________________________________ > 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 zubin at well-typed.com Sun Jan 23 08:02:15 2022 From: zubin at well-typed.com (Zubin Duggal) Date: Sun, 23 Jan 2022 13:32:15 +0530 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: References: <20211225202027.jxlafyybul4bltfb@zubin-msi> Message-ID: <20220123080215.b4bvjuxkvw5miohb@zubin-msi> > - More serious: why was Win32 major bumped from 2.10 to 2.12? > - this breaks foundation, hence current Stackage Nightly is kind of > broken for Windows now: > https://github.com/commercialhaskell/stackage/issues/6400 We needed to bump Win32 as per a request from the maintainer made at https://gitlab.haskell.org/ghc/ghc/-/issues/20017 Bumping it from 2.10.0 to 2.10.1.0 ran into https://github.com/haskell/win32/issues/174, which was fixed by https://github.com/haskell/win32/pull/175 Given this, our options at the time were: 1) Backport pull request #175 to 2.10.1 and wait for a new release of Win32 2) Revert https://github.com/haskell/win32/pull/160 in Win32 2.10, which is what caused WinIO/#174 3) Use Win32 2.12.0.1, which contains the requested fix(ghc/#20017), as well as the explicit exports added by #175, along with a few other minor changes from Win32 2.11 which I don't think are responsible for any of the pain discussed in the stackage issue. I made the decision to go with option 3 in the interests of getting the release out. However, if I understand correctly, we would still end up with the same problems as brought up in the stackage issue if we went with option 1. We might have avoided some of this pain if we went with option 2 and reverted the offending commits from WinIO 2.10 instead of using explicit import lists. But removing features from a major release of a library didn't seem like a good idea at a time, and would have delayed the 9.0.2 release even more. I hope this makes the reasoning for the decision clearer, and I do apologise for any pain caused. I did believe that under the circumstances bumping WinIO to 2.12.0.1 was the best way forward. Perhaps option 2 would have been better in retrospect, but at the time the benefits for such a change (in particular the regression in functionality) in a major release of Win32 were not so clear. Cheers, Zubin From zubin at well-typed.com Sun Jan 23 08:07:26 2022 From: zubin at well-typed.com (Zubin) Date: Sun, 23 Jan 2022 13:37:26 +0530 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: <20220123080215.b4bvjuxkvw5miohb@zubin-msi> References: <20211225202027.jxlafyybul4bltfb@zubin-msi> <20220123080215.b4bvjuxkvw5miohb@zubin-msi> Message-ID: <283FB15D-E3DE-49FE-B7DF-986D66D04F38@well-typed.com> I wrote WinIO a couple of times when I meant to type Win32. Sorry! On 23 January 2022 1:32:15 pm IST, Zubin Duggal wrote: > >> - More serious: why was Win32 major bumped from 2.10 to 2.12? >> - this breaks foundation, hence current Stackage Nightly is kind of >> broken for Windows now: >> https://github.com/commercialhaskell/stackage/issues/6400 > >We needed to bump Win32 as per a request from the maintainer made at >https://gitlab.haskell.org/ghc/ghc/-/issues/20017 > >Bumping it from 2.10.0 to 2.10.1.0 ran into >https://github.com/haskell/win32/issues/174, which was fixed by >https://github.com/haskell/win32/pull/175 > >Given this, our options at the time were: > >1) Backport pull request #175 to 2.10.1 and wait for a new release of Win32 > >2) Revert https://github.com/haskell/win32/pull/160 in Win32 2.10, > which is what caused WinIO/#174 > >3) Use Win32 2.12.0.1, which contains the requested fix(ghc/#20017), as > well as the explicit exports added by #175, along with a few other minor > changes from Win32 2.11 which I don't think are responsible for any of > the pain discussed in the stackage issue. > >I made the decision to go with option 3 in the interests of getting the >release out. > >However, if I understand correctly, we would still end up with the same >problems as brought up in the stackage issue if we went with option 1. > >We might have avoided some of this pain if we went with option 2 and >reverted the offending commits from WinIO 2.10 instead of using explicit >import lists. But removing features from a major release of a library >didn't seem like a good idea at a time, and would have delayed the 9.0.2 >release even more. > >I hope this makes the reasoning for the decision clearer, and I >do apologise for any pain caused. I did believe that under the >circumstances bumping WinIO to 2.12.0.1 was the best way forward. >Perhaps option 2 would have been better in retrospect, but at the >time the benefits for such a change (in particular the regression in >functionality) in a major release of Win32 were not so clear. > >Cheers, >Zubin >_______________________________________________ >Glasgow-haskell-users mailing list >Glasgow-haskell-users at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users From juhpetersen at gmail.com Sun Jan 23 09:12:57 2022 From: juhpetersen at gmail.com (Jens Petersen) Date: Sun, 23 Jan 2022 17:12:57 +0800 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: References: <20211225202027.jxlafyybul4bltfb@zubin-msi> Message-ID: On Sun, 23 Jan 2022 at 15:40, David Feuer wrote: > Could you explain what you mean about the containers source not being > "clean"? > I forgot to say "in the source tarball" explicitly. If you look in libraries/containers/containers/dist-install, you can see what I am talking about. (I first discovered this because it broke the Fedora build - so I just remove it before building.) Jens On Sun, Jan 23, 2022, 2:31 AM Jens Petersen wrote: > >> First of all a big thank you and congratulations on the highly >> anticipated 9.0.2 release. >> >> I have been putting off this mail for a while: >> I actually built it last month right away in Fedora's new ghc9.0 package >> (available now for all current Fedora releases). >> Also Stackage Nightly (primarily thanks to Adam Bergmark) was updated to >> 9.0.2, since nightly-2022-01-10. :-) >> >> However two points I wanted to mention: >> >> - firstly (minor), the libraries/containers source is not clean >> (which explains why the tarball is so big) >> >> >> - More serious: why was Win32 major bumped from 2.10 to 2.12? >> - this breaks foundation, hence current Stackage Nightly is kind >> of broken for Windows now: >> https://github.com/commercialhaskell/stackage/issues/6400 >> >> I can't really see any good way to resolve this in the short term. >> >> Thanks, Jens >> >> >> On Sun, 26 Dec 2021 at 04:23, Zubin Duggal wrote: >> >>> The GHC developers are very happy to at long last announce the >>> availability of GHC 9.0.2. Binary distributions, source distributions, >>> and documentation are available at the >>> [usual place](https://downloads.haskell.org/ghc/9.0.2/). >>> >>> _______________________________________________ >> 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 david.feuer at gmail.com Sun Jan 23 13:45:38 2022 From: david.feuer at gmail.com (David Feuer) Date: Sun, 23 Jan 2022 08:45:38 -0500 Subject: [Haskell] [ANNOUNCE] GHC 9.0.2 released In-Reply-To: References: <20211225202027.jxlafyybul4bltfb@zubin-msi> Message-ID: There's no such directory in the Hackage or GitHub source. I guess it must have crept in on the GHC side? On Sun, Jan 23, 2022, 4:13 AM Jens Petersen wrote: > On Sun, 23 Jan 2022 at 15:40, David Feuer wrote: > >> Could you explain what you mean about the containers source not being >> "clean"? >> > > I forgot to say "in the source tarball" explicitly. > If you look in libraries/containers/containers/dist-install, you can see > what I am talking about. > (I first discovered this because it broke the Fedora build - so I just > remove it before building.) > > Jens > > On Sun, Jan 23, 2022, 2:31 AM Jens Petersen wrote: >> >>> First of all a big thank you and congratulations on the highly >>> anticipated 9.0.2 release. >>> >>> I have been putting off this mail for a while: >>> I actually built it last month right away in Fedora's new ghc9.0 package >>> (available now for all current Fedora releases). >>> Also Stackage Nightly (primarily thanks to Adam Bergmark) was updated to >>> 9.0.2, since nightly-2022-01-10. :-) >>> >>> However two points I wanted to mention: >>> >>> - firstly (minor), the libraries/containers source is not clean >>> (which explains why the tarball is so big) >>> >>> >>> - More serious: why was Win32 major bumped from 2.10 to 2.12? >>> - this breaks foundation, hence current Stackage Nightly is kind >>> of broken for Windows now: >>> https://github.com/commercialhaskell/stackage/issues/6400 >>> >>> I can't really see any good way to resolve this in the short term. >>> >>> Thanks, Jens >>> >>> >>> On Sun, 26 Dec 2021 at 04:23, Zubin Duggal wrote: >>> >>>> The GHC developers are very happy to at long last announce the >>>> availability of GHC 9.0.2. Binary distributions, source distributions, >>>> and documentation are available at the >>>> [usual place](https://downloads.haskell.org/ghc/9.0.2/). >>>> >>>> _______________________________________________ >>> 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: