From djsamperi at gmail.com Fri Oct 1 15:23:45 2021 From: djsamperi at gmail.com (Dominick Samperi) Date: Fri, 1 Oct 2021 11:23:45 -0400 Subject: Stack lock issue Message-ID: Hi, Stack install does its thing in some hashed directory under .stack-work by default, but I want to write to /bin as part of the configure process. I'm trying to do this as follows: -- configure file contains: cd $(stack path --project-root) echo "..." > .bin/foo.sh cd - > cd > stack install I'm doing this under Windows with the born shell in my path. Problem: the use of stack to find the project-root directory is blocked waiting for the outer stack to terminate! This may have something to do with Windows "Device or resource busy" lock. Is there a better way? Thanks, Dominick Virus-free. www.avg.com <#DAB4FAD8-2DD7-40BB-A1B8-4E2AA1F9FDF2> -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Fri Oct 1 20:00:18 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Fri, 01 Oct 2021 16:00:18 -0400 Subject: Prettyprinting GHC.Stg.Syntax.StgOp Message-ID: <20211001200018.EDFCE2C2A23@homedog.cs.tufts.edu> Type StgOp and its constructors are exported from module GHC.Stg.Syntax. But the prettyprinting function pprStgOp is not exported. I'm thinking of exporting the function and also of defining an instance of Outputable. Is there any reason not to? If this sounds OK to people, I'll make a PR. Norman From ben at smart-cactus.org Sat Oct 2 15:23:23 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Sat, 02 Oct 2021 11:23:23 -0400 Subject: Prettyprinting GHC.Stg.Syntax.StgOp In-Reply-To: <20211001200018.EDFCE2C2A23@homedog.cs.tufts.edu> References: <20211001200018.EDFCE2C2A23@homedog.cs.tufts.edu> Message-ID: <8735pjjvsb.fsf@smart-cactus.org> Norman Ramsey writes: > Type StgOp and its constructors are exported from module > GHC.Stg.Syntax. But the prettyprinting function pprStgOp is not > exported. I'm thinking of exporting the function and also > of defining an instance of Outputable. Is there any reason not to? > > If this sounds OK to people, I'll make a PR. > An Outputable instance seems quite reasonable to me. Exporting pprStgOp seems less necessary but I wouldn't object. 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 lexi.lambda at gmail.com Sun Oct 3 16:19:47 2021 From: lexi.lambda at gmail.com (Alexis King) Date: Sun, 3 Oct 2021 11:19:47 -0500 Subject: GHC indecisive whether matching on GADT constructors in arrow notation is allowed Message-ID: Hi, I’ve been working on bringing my reimplementation of arrow notation back up to date, and I’ve run into some confusion about the extent to which arrow notation is “supposed” to support matching on GADT constructors. Note [Arrows and patterns] in GHC.Tc.Gen.Pat suggests they aren’t supposed to be supported at all, which is what I would essentially expect. But issues #17423 and #18950 provide examples of using GADT constructors in arrow notation, and there seems to be some expectation that in fact they *ought* to be supported, and some recently-added test cases verify that’s the case. But this is quite odd, because it means the arrows test suite now includes test cases that verify both that this is supported *and* that it isn’t… and all of them pass! Here’s my understanding of the status quo: - Matching on constructors that bind bona fide existential variables is not allowed, and this is verified by the arrowfail004 test case, which involves the following program: data T = forall a. T a panic :: (Arrow arrow) => arrow T T panic = proc (T x) -> do returnA -< T x This program is rejected with the following error message: arrowfail004.hs:12:15: Proc patterns cannot use existential or GADT data constructors In the pattern: T x - Despite the previous point, matching on constructors that bind evidence is allowed. This is enshrined in test cases T15175, T17423, and T18950, which match on constructors like these: data DecoType a where DecoBool :: Maybe (String, String) -> Maybe (Int, Int) -> DecoType Bool data Point a where Point :: RealFloat a => a -> Point a This seems rather contradictory to me. I don’t think there’s much of a meaningful distinction between these types of matches, as they create precisely the same set of challenges from the Core point of view… right? And even if I’m wrong, the error message in arrowfail004 seems rather misleading, since I would definitely call DecoBool and Point above “GADT data constructors”. So what’s the intended story here? Is matching on GADT constructors in arrow notation supposed to be allowed or not? (I suspect this is really just yet another case of “nobody really knows what’s ‘supposed’ to happen with arrow notation,” but I figured I might as well ask out of hopefulness that someone has some idea.) Thanks, Alexis -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Sun Oct 3 17:40:35 2021 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Sun, 3 Oct 2021 18:40:35 +0100 Subject: Optics? Message-ID: Hi all I am working on a variant of the exact printer which updates the annotation locations from the `EpaSpan` version to the `EpaDelta` version, as the printing happens data EpaLocation = EpaSpan RealSrcSpan | EpaDelta DeltaPos The function doing the work is this markAnnKw :: (Monad m, Monoid w) => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) -> AnnKeywordId -> EP w m (EpAnn a) which gets an annotation, a function to pull a specific location out, and one to update it. I do not know much about lenses, but have a feeling that I could simplify things by using one. Can anyone give me any pointers? Alan -------------- next part -------------- An HTML attachment was scrubbed... URL: From vladislav at serokell.io Sun Oct 3 17:52:04 2021 From: vladislav at serokell.io (Vladislav Zavialov) Date: Sun, 3 Oct 2021 20:52:04 +0300 Subject: Optics? In-Reply-To: References: Message-ID: <5067D9E3-43AD-4244-9638-65588C1ED040@serokell.io> Hi Alan, Your pair of functions can be packaged up as a single function, so that getEpa :: a -> EpaLocation setEpa :: a -> EpaLocation -> a becomes lensEpa :: forall f. Functor f => (EpaLocation -> f EpaLocation) -> (a -> f a) And the get/set parts can be recovered by instantiating `f` to either Identity or Const. The nice thing about lenses is that they compose, so that if you need nested access, you could define several lenses, compose them together, and then reach deep into a data structure. Then lenses might offer some simplification. Otherwise, an ordinary getter/setter pair is just as good. - Vlad > On 3 Oct 2021, at 20:40, Alan & Kim Zimmerman wrote: > > Hi all > > I am working on a variant of the exact printer which updates the annotation locations from the `EpaSpan` version to the `EpaDelta` version, as the printing happens > > data EpaLocation = EpaSpan RealSrcSpan > | EpaDelta DeltaPos > > The function doing the work is this > > markAnnKw :: (Monad m, Monoid w) > => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) -> AnnKeywordId -> EP w m (EpAnn a) > > which gets an annotation, a function to pull a specific location out, and one to update it. > > I do not know much about lenses, but have a feeling that I could simplify things by using one. > > Can anyone give me any pointers? > > Alan > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From alan.zimm at gmail.com Sun Oct 3 22:34:21 2021 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Sun, 3 Oct 2021 23:34:21 +0100 Subject: Optics? In-Reply-To: <5067D9E3-43AD-4244-9638-65588C1ED040@serokell.io> References: <5067D9E3-43AD-4244-9638-65588C1ED040@serokell.io> Message-ID: With a pointer from Vlad and some study of the lens tutorial, I made a proof of concept at [1]. I am deliberately not using the existing lens library as I envisage this code ending up in GHC. Alan [1] https://github.com/alanz/ghc-exactprint/blob/f218e211c47943c216a2e25d7855f98a0355f6b8/src/Language/Haskell/GHC/ExactPrint/ExactPrint.hs#L689-L723 On Sun, 3 Oct 2021 at 18:52, Vladislav Zavialov wrote: > Hi Alan, > > Your pair of functions can be packaged up as a single function, so that > > getEpa :: a -> EpaLocation > setEpa :: a -> EpaLocation -> a > > becomes > > lensEpa :: forall f. Functor f => (EpaLocation -> f EpaLocation) > -> (a -> f a) > > And the get/set parts can be recovered by instantiating `f` to either > Identity or Const. > > The nice thing about lenses is that they compose, so that if you need > nested access, you could define several lenses, compose them together, and > then reach deep into a data structure. Then lenses might offer some > simplification. Otherwise, an ordinary getter/setter pair is just as good. > > - Vlad > > > On 3 Oct 2021, at 20:40, Alan & Kim Zimmerman > wrote: > > > > Hi all > > > > I am working on a variant of the exact printer which updates the > annotation locations from the `EpaSpan` version to the `EpaDelta` version, > as the printing happens > > > > data EpaLocation = EpaSpan RealSrcSpan > > | EpaDelta DeltaPos > > > > The function doing the work is this > > > > markAnnKw :: (Monad m, Monoid w) > > => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) -> > AnnKeywordId -> EP w m (EpAnn a) > > > > which gets an annotation, a function to pull a specific location out, > and one to update it. > > > > I do not know much about lenses, but have a feeling that I could > simplify things by using one. > > > > Can anyone give me any pointers? > > > > Alan > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From sgraf1337 at gmail.com Mon Oct 4 06:54:23 2021 From: sgraf1337 at gmail.com (Sebastian Graf) Date: Mon, 4 Oct 2021 08:54:23 +0200 Subject: Optics? In-Reply-To: References: <5067D9E3-43AD-4244-9638-65588C1ED040@serokell.io> Message-ID: Hi Alan, hi Vlad, Yes, one thing that is nice about van Laarhoven lenses is that you don't actually need to depend on anything if all you want is export lenses in your API. We have also discussed using a small lens library in the past, in https://gitlab.haskell.org/ghc/ghc/-/issues/18693. The MVP would be to just depend on the Lens module defined in newer versions of Cabal. Sebastian Am Mo., 4. Okt. 2021 um 00:35 Uhr schrieb Alan & Kim Zimmerman < alan.zimm at gmail.com>: > With a pointer from Vlad and some study of the lens tutorial, I made a > proof of concept at [1]. > I am deliberately not using the existing lens library as I envisage this > code ending up in GHC. > > Alan > > [1] > https://github.com/alanz/ghc-exactprint/blob/f218e211c47943c216a2e25d7855f98a0355f6b8/src/Language/Haskell/GHC/ExactPrint/ExactPrint.hs#L689-L723 > > > > On Sun, 3 Oct 2021 at 18:52, Vladislav Zavialov > wrote: > >> Hi Alan, >> >> Your pair of functions can be packaged up as a single function, so that >> >> getEpa :: a -> EpaLocation >> setEpa :: a -> EpaLocation -> a >> >> becomes >> >> lensEpa :: forall f. Functor f => (EpaLocation -> f EpaLocation) >> -> (a -> f a) >> >> And the get/set parts can be recovered by instantiating `f` to either >> Identity or Const. >> >> The nice thing about lenses is that they compose, so that if you need >> nested access, you could define several lenses, compose them together, and >> then reach deep into a data structure. Then lenses might offer some >> simplification. Otherwise, an ordinary getter/setter pair is just as good. >> >> - Vlad >> >> > On 3 Oct 2021, at 20:40, Alan & Kim Zimmerman >> wrote: >> > >> > Hi all >> > >> > I am working on a variant of the exact printer which updates the >> annotation locations from the `EpaSpan` version to the `EpaDelta` version, >> as the printing happens >> > >> > data EpaLocation = EpaSpan RealSrcSpan >> > | EpaDelta DeltaPos >> > >> > The function doing the work is this >> > >> > markAnnKw :: (Monad m, Monoid w) >> > => EpAnn a -> (a -> EpaLocation) -> (a -> EpaLocation -> a) -> >> AnnKeywordId -> EP w m (EpAnn a) >> > >> > which gets an annotation, a function to pull a specific location out, >> and one to update it. >> > >> > I do not know much about lenses, but have a feeling that I could >> simplify things by using one. >> > >> > Can anyone give me any pointers? >> > >> > Alan >> > >> > _______________________________________________ >> > ghc-devs mailing list >> > ghc-devs at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 4 09:29:42 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 4 Oct 2021 09:29:42 +0000 Subject: Instantiation of overloaded definition *in Core* Message-ID: PUBLIC Hi, I'd like to instantiate Core definitions. For example, suppose I have the following Core definition: foo :: forall m a b. Monad m => m a -> m b -> m b foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... Now let's say I'd like to instantiate it for m ~ IO. It is quite straightforward to go from the above to: foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ... However, I would like to go all the way to: foo_IO :: forall a b. IO a -> IO b -> IO b foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ... Because instances are coherent, it should be sound to replace all occurrences of $d with "the" dictionary for Monad IO. However, the places I've found for this kind of query seem to live in the typechecker. How do I access this information while working with Core? Thanks, Gergo This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Oct 4 11:29:22 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 4 Oct 2021 11:29:22 +0000 Subject: Instantiation of overloaded definition *in Core* In-Reply-To: References: Message-ID: You can look it up in the class instance environment, which the Simplifier does have access to it. That's relatively easy when you have a simple dictionary like (Monad IO). But if you want (Eq [Int]) you first of all have to look up the (Eq [a]) dictionary, then the Eq Int dictionary, and apply the former to the latter. We don't (yet) have a simple API to do that, although it would not be hard to create one. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs Sent: 04 October 2021 10:30 To: 'GHC' Cc: Montelatici, Raphael Laurent Subject: Instantiation of overloaded definition *in Core* PUBLIC Hi, I'd like to instantiate Core definitions. For example, suppose I have the following Core definition: foo :: forall m a b. Monad m => m a -> m b -> m b foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... Now let's say I'd like to instantiate it for m ~ IO. It is quite straightforward to go from the above to: foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ... However, I would like to go all the way to: foo_IO :: forall a b. IO a -> IO b -> IO b foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ... Because instances are coherent, it should be sound to replace all occurrences of $d with "the" dictionary for Monad IO. However, the places I've found for this kind of query seem to live in the typechecker. How do I access this information while working with Core? Thanks, Gergo This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lexi.lambda at gmail.com Mon Oct 4 19:19:27 2021 From: lexi.lambda at gmail.com (Alexis King) Date: Mon, 4 Oct 2021 14:19:27 -0500 Subject: Arrow notation, existentials, and TcType demotion Message-ID: Hello, As I mentioned in a previous email , GHC seems currently somewhat uncertain about whether or not matching on GADTs is permitted in arrow notation. Sam Derbyshire suggested on Twitter that we probably do, ideally speaking, want to support them. Unfortunately, I am confident that the existing implementation is *not* up to this task, as I have now demonstrated in issues #20469 and #20470 . The latter of those two issues is particularly challenging to solve, as it highlights the sorts of tricky interactions that can arise when arrow notation is mixed with existential quantification. To give an example, suppose we have the following datatypes: data A where A :: a -> B a -> A data B a where B :: B () And suppose we have the following proc expression: proc a -> case a of A x B -> id -< x The match on the A constructor introduces a locally-scoped skolem, and even though the use of id appears on the RHS, it is *not* actually within the match’s scope—rather, its scope is that of the overall proc expression. This makes it tricky to maintain typechecker invariants, as introduced metavariables must not accidentally leak into the outer scope via these strangely-scoped expressions. For example, when typechecking the above expression, we’ll increment tcl_tclevel before typechecking the id -< x command, and we may introduce fresh metavariables while doing so. This means we may end up with an expected type for id that looks like this: a1[tau:1] -> a2[tau:1] However, when we actually check id against that type, we must do so in a context where tcl_tclevel is 0, not 1. This violates WantedInv from Note [TcLevel invariants] in GHC.Tc.Utils.TcType. This means we need to do a three-step process to properly check id’s type: 1. Synthesize a new metavariable a3[tau:0]. 2. Emit [W] a3[tau:0] ~ (a1[tau:1] -> a2[tau:1]) within the arrow scope, i.e. where tcl_tclevel = 1. 3. Check id against a3[tau:0]. Discerning readers may note that this looks *awfully* similar to the process by which we promote a type via promoteTcType, as described in Note [Promoting a type] in GHC.Tc.Utils.TcMType. However, in this case, we aren’t really promoting a type, but *demoting* it—we ultimately want to decrease its level, not increase it. However, it seems to me that the process of doing this demotion is in fact handled perfectly fine by promoteTcType. So my question is twofold: 1. Is my reasoning about what to do here correct? 2. Is there any harm in using promoteTcType to do this demotion? Thanks, Alexis -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Tue Oct 5 16:12:54 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Tue, 5 Oct 2021 16:12:54 +0000 Subject: GHC indecisive whether matching on GADT constructors in arrow notation is allowed In-Reply-To: References: Message-ID: <010f017c513ab5a2-63ed4ac9-6a34-4499-820d-113f462ea5da-000000@us-east-2.amazonses.com> I think the real difference is whether new type variables are brought into scope. It seems that GHC can't deal with a proc-pattern-match that introduces type variables, but it *can* deal with introduced constraints. I have no idea *why* this is the case, but it seems a plausible (if accidental) resting place for the implementation. Richard > On Oct 3, 2021, at 12:19 PM, Alexis King wrote: > > Hi, > > I’ve been working on bringing my reimplementation of arrow notation back up to date, and I’ve run into some confusion about the extent to which arrow notation is “supposed” to support matching on GADT constructors. Note [Arrows and patterns] in GHC.Tc.Gen.Pat suggests they aren’t supposed to be supported at all, which is what I would essentially expect. But issues #17423 and #18950 provide examples of using GADT constructors in arrow notation, and there seems to be some expectation that in fact they ought to be supported, and some recently-added test cases verify that’s the case. > > But this is quite odd, because it means the arrows test suite now includes test cases that verify both that this is supported and that it isn’t… and all of them pass! Here’s my understanding of the status quo: > > Matching on constructors that bind bona fide existential variables is not allowed, and this is verified by the arrowfail004 test case, which involves the following program: > > data T = forall a. T a > > panic :: (Arrow arrow) => arrow T T > panic = proc (T x) -> do returnA -< T x > This program is rejected with the following error message: > > arrowfail004.hs:12:15: > Proc patterns cannot use existential or GADT data constructors > In the pattern: T x > Despite the previous point, matching on constructors that bind evidence is allowed. This is enshrined in test cases T15175, T17423, and T18950, which match on constructors like these: > > data DecoType a where > DecoBool :: Maybe (String, String) -> Maybe (Int, Int) -> DecoType Bool > data Point a where > Point :: RealFloat a => a -> Point a > This seems rather contradictory to me. I don’t think there’s much of a meaningful distinction between these types of matches, as they create precisely the same set of challenges from the Core point of view… right? And even if I’m wrong, the error message in arrowfail004 seems rather misleading, since I would definitely call DecoBool and Point above “GADT data constructors”. > > So what’s the intended story here? Is matching on GADT constructors in arrow notation supposed to be allowed or not? (I suspect this is really just yet another case of “nobody really knows what’s ‘supposed’ to happen with arrow notation,” but I figured I might as well ask out of hopefulness that someone has some idea.) > > Thanks, > Alexis > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg.grenrus at iki.fi Tue Oct 5 16:49:09 2021 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Tue, 5 Oct 2021 19:49:09 +0300 Subject: GHC indecisive whether matching on GADT constructors in arrow notation is allowed In-Reply-To: <010f017c513ab5a2-63ed4ac9-6a34-4499-820d-113f462ea5da-000000@us-east-2.amazonses.com> References: <010f017c513ab5a2-63ed4ac9-6a34-4499-820d-113f462ea5da-000000@us-east-2.amazonses.com> Message-ID: <031a7332-61f9-1f10-a4b1-0fd2f23a133b@iki.fi> A simple desugaring example may illustrate:     {-# LANGUAGE Arrows, GADTs #-}     import Control.Arrow     data X a where       X :: Bool -> Int -> X (Bool, Int)     ex1 :: Arrow a => a (X x) (Int, Bool)     ex1 = proc (X b i) -> returnA -< (i, b)     ex1expl :: Arrow a => a (X x) (Int, Bool)     ex1expl =         arr f >>> -- pattern match         arr g >>> -- expression         returnA       where         f :: X a -> (Bool, Int)         f (X b i) = (b, i)         g :: (Bool, Int) -> (Int, Bool)         g (b, i) = (i, b) If we want to desugar Alexis' example     data T where         T :: a -> T     panic :: (Arrow arrow) => arrow T T     panic = proc (T x) -> do returnA -< T x which has the same shape, what would the type of `f` be?     f :: T -> a -- doesn't work If we had sigmas, i.e. dependent pairs and type level lambdas, we could have     f :: T -> Sigma Type (\a -> a) -- a pair like (Bool, Int) but fancier i.e. the explicit desugaring could look like     panicExplicit :: (Arrow arrow) => arrow T T     panicExplicit =         arr f >>>         arr g >>>         returnA       where         f :: T -> Sigma Type (\a -> a)         f (T @a x) = (@a, x)         g :: Sigma Type (\a -> a)         g (@a, x) = T @a x My gut feeling says that the original arrow desugaring would just work, but instead of tuples for context, we'd need to use telescopes. Not that earth-shattering of a generalization. The evidence could be explicitly bound already today, but I guess it's not, and simply thrown away:     {-# LANGUAGE Arrows, GADTs, ConstraintKinds #-}     import Control.Arrow     data Showable a where         Showable :: Show a => a -> Showable a     data Dict c where         Dict :: c => Dict c     ex2explicit :: Arrow a => a (Showable x) (Showable x)     ex2explicit =         arr f >>> -- pattern match         arr g >>> -- expression         returnA        where         f :: Showable x -> (x, Dict (Show x))         f (Showable x) = (x, Dict)         g :: (x, Dict (Show x)) -> Showable x         g (x, Dict) = Showable x The     ex2 :: Arrow a => a (Showable x) (Showable x)     ex2 = proc (Showable x) -> returnA -< Showable x works today, surprisingly. Looks like GHC does something as above, if I read the -ddump-ds output correctly:     ex2       :: forall (a :: * -> * -> *) x.          Arrow a =>          a (Showable x) (Showable x)     [LclIdX]     ex2       = \ (@ (a_a2ja :: * -> * -> *))           (@ x_a2jb)           ($dArrow_a2jd :: Arrow a_a2ja) ->           break<1>()           let {             arr' :: forall b c. (b -> c) -> a_a2ja b c             [LclId]             arr' = arr @ a_a2ja $dArrow_a2jm } in           let {             (>>>>) :: forall a b c. a_a2ja a b -> a_a2ja b c -> a_a2ja a c             [LclId]             (>>>>) = GHC.Desugar.>>> @ a_a2ja $dArrow_a2jn } in           (>>>>)             @ (Showable x_a2jb)             @ ((Show x_a2jb, x_a2jb), ())             @ (Showable x_a2jb)             (arr'                @ (Showable x_a2jb)                @ ((Show x_a2jb, x_a2jb), ()) -- this is interesting                (\ (ds_d2kY :: Showable x_a2jb) ->                   case ds_d2kY of { Showable $dShow_a2je x_a2hL ->                   (($dShow_a2je, x_a2hL), ghc-prim-0.5.3:GHC.Tuple.())                   }))             ((>>>>)                @ ((Show x_a2jb, x_a2jb), ())                @ (Showable x_a2jb)                @ (Showable x_a2jb)                (arr'                   @ ((Show x_a2jb, x_a2jb), ())                   @ (Showable x_a2jb)                   (\ (ds_d2kX :: ((Show x_a2jb, x_a2jb), ())) ->                      case ds_d2kX of { (ds_d2kW, _ [Occ=Dead]) ->                      case ds_d2kW of { ($dShow_a2jl, x_a2hL) ->                      break<0>() Main.Showable @ x_a2jb $dShow_a2jl x_a2hL                      }                      }))                (returnA @ a_a2ja @ (Showable x_a2jb) $dArrow_a2jd)) - Oleg On 5.10.2021 19.12, Richard Eisenberg wrote: > I think the real difference is whether new type variables are brought > into scope. It seems that GHC can't deal with a proc-pattern-match > that introduces type variables, but it *can* deal with introduced > constraints. I have no idea *why* this is the case, but it seems a > plausible (if accidental) resting place for the implementation. > > Richard > >> On Oct 3, 2021, at 12:19 PM, Alexis King > > wrote: >> >> Hi, >> >> I’ve been working on bringing my reimplementation of arrow notation >> back up to date, and I’ve run into some confusion about the extent to >> which arrow notation is “supposed” to support matching on GADT >> constructors. |Note [Arrows and patterns]| in |GHC.Tc.Gen.Pat| >> suggests they aren’t supposed to be supported at all, which is what I >> would essentially expect. But issues #17423 >> and #18950 >> provide examples >> of using GADT constructors in arrow notation, and there seems to be >> some expectation that in fact they /ought/ to be supported, and some >> recently-added test cases verify that’s the case. >> >> But this is quite odd, because it means the arrows test suite now >> includes test cases that verify both that this is supported /and/ >> that it isn’t… and all of them pass! Here’s my understanding of the >> status quo: >> >> * >> >> Matching on constructors that bind bona fide existential >> variables is not allowed, and this is verified by the >> |arrowfail004| test case, which involves the following program: >> >> |data T = forall a. T a panic :: (Arrow arrow) => arrow T T panic >> = proc (T x) -> do returnA -< T x| >> >> This program is rejected with the following error message: >> >> |arrowfail004.hs:12:15: Proc patterns cannot use existential or >> GADT data constructors In the pattern: T x| >> * >> >> Despite the previous point, matching on constructors that bind >> evidence is allowed. This is enshrined in test cases |T15175|, >> |T17423|, and |T18950|, which match on constructors like these: >> >> |data DecoType a where DecoBool :: Maybe (String, String) -> >> Maybe (Int, Int) -> DecoType Bool data Point a where Point :: >> RealFloat a => a -> Point a| >> >> This seems rather contradictory to me. I don’t think there’s much of >> a meaningful distinction between these types of matches, as they >> create precisely the same set of challenges from the Core point of >> view… right? And even if I’m wrong, the error message in >> |arrowfail004| seems rather misleading, since I would definitely call >> |DecoBool| and |Point| above “GADT data constructors”. >> >> So what’s the intended story here? Is matching on GADT constructors >> in arrow notation supposed to be allowed or not? (I suspect this is >> really just yet another case of “nobody really knows what’s >> ‘supposed’ to happen with arrow notation,” but I figured I might as >> well ask out of hopefulness that someone has some idea.) >> >> Thanks, >> Alexis >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From lexi.lambda at gmail.com Tue Oct 5 19:03:15 2021 From: lexi.lambda at gmail.com (Alexis King) Date: Tue, 5 Oct 2021 14:03:15 -0500 Subject: GHC indecisive whether matching on GADT constructors in arrow notation is allowed In-Reply-To: <031a7332-61f9-1f10-a4b1-0fd2f23a133b@iki.fi> References: <010f017c513ab5a2-63ed4ac9-6a34-4499-820d-113f462ea5da-000000@us-east-2.amazonses.com> <031a7332-61f9-1f10-a4b1-0fd2f23a133b@iki.fi> Message-ID: I have already discussed this particular issue at some length in #20470 , and I propose a possible desugaring, using higher-rank lambdas to encode existential quantification, in a comment . This is fine, since we only need to desugar to Core, not source Haskell. Alexis On Tue, Oct 5, 2021 at 11:50 AM Oleg Grenrus wrote: > A simple desugaring example may illustrate: > > {-# LANGUAGE Arrows, GADTs #-} > > import Control.Arrow > > data X a where > X :: Bool -> Int -> X (Bool, Int) > > ex1 :: Arrow a => a (X x) (Int, Bool) > ex1 = proc (X b i) -> returnA -< (i, b) > > ex1expl :: Arrow a => a (X x) (Int, Bool) > ex1expl = > arr f >>> -- pattern match > arr g >>> -- expression > returnA > where > f :: X a -> (Bool, Int) > f (X b i) = (b, i) > > g :: (Bool, Int) -> (Int, Bool) > g (b, i) = (i, b) > > If we want to desugar Alexis' example > > data T where > T :: a -> T > > panic :: (Arrow arrow) => arrow T T > panic = proc (T x) -> do returnA -< T x > > which has the same shape, what would the type of `f` be? > > f :: T -> a -- doesn't work > > If we had sigmas, i.e. dependent pairs and type level lambdas, we could > have > > f :: T -> Sigma Type (\a -> a) -- a pair like (Bool, Int) but fancier > > i.e. the explicit desugaring could look like > > panicExplicit :: (Arrow arrow) => arrow T T > panicExplicit = > arr f >>> > arr g >>> > returnA > where > f :: T -> Sigma Type (\a -> a) > f (T @a x) = (@a, x) > > g :: Sigma Type (\a -> a) > g (@a, x) = T @a x > > My gut feeling says that the original arrow desugaring would just work, > but instead of tuples for context, we'd need to use telescopes. > Not that earth-shattering of a generalization. > > The evidence could be explicitly bound already today, > but I guess it's not, and simply thrown away: > > {-# LANGUAGE Arrows, GADTs, ConstraintKinds #-} > > import Control.Arrow > > data Showable a where > Showable :: Show a => a -> Showable a > > data Dict c where > Dict :: c => Dict c > > ex2explicit :: Arrow a => a (Showable x) (Showable x) > ex2explicit = > arr f >>> -- pattern match > arr g >>> -- expression > returnA > where > f :: Showable x -> (x, Dict (Show x)) > f (Showable x) = (x, Dict) > > g :: (x, Dict (Show x)) -> Showable x > g (x, Dict) = Showable x > > The > > ex2 :: Arrow a => a (Showable x) (Showable x) > ex2 = proc (Showable x) -> returnA -< Showable x > > works today, surprisingly. Looks like GHC does something as above, > if I read the -ddump-ds output correctly: > > ex2 > :: forall (a :: * -> * -> *) x. > Arrow a => > a (Showable x) (Showable x) > [LclIdX] > ex2 > = \ (@ (a_a2ja :: * -> * -> *)) > (@ x_a2jb) > ($dArrow_a2jd :: Arrow a_a2ja) -> > break<1>() > let { > arr' :: forall b c. (b -> c) -> a_a2ja b c > [LclId] > arr' = arr @ a_a2ja $dArrow_a2jm } in > let { > (>>>>) :: forall a b c. a_a2ja a b -> a_a2ja b c -> a_a2ja a c > [LclId] > (>>>>) = GHC.Desugar.>>> @ a_a2ja $dArrow_a2jn } in > (>>>>) > @ (Showable x_a2jb) > @ ((Show x_a2jb, x_a2jb), ()) > @ (Showable x_a2jb) > (arr' > @ (Showable x_a2jb) > @ ((Show x_a2jb, x_a2jb), ()) -- this is interesting > (\ (ds_d2kY :: Showable x_a2jb) -> > case ds_d2kY of { Showable $dShow_a2je x_a2hL -> > (($dShow_a2je, x_a2hL), ghc-prim-0.5.3:GHC.Tuple.()) > })) > ((>>>>) > @ ((Show x_a2jb, x_a2jb), ()) > @ (Showable x_a2jb) > @ (Showable x_a2jb) > (arr' > @ ((Show x_a2jb, x_a2jb), ()) > @ (Showable x_a2jb) > (\ (ds_d2kX :: ((Show x_a2jb, x_a2jb), ())) -> > case ds_d2kX of { (ds_d2kW, _ [Occ=Dead]) -> > case ds_d2kW of { ($dShow_a2jl, x_a2hL) -> > break<0>() Main.Showable @ x_a2jb $dShow_a2jl x_a2hL > } > })) > (returnA @ a_a2ja @ (Showable x_a2jb) $dArrow_a2jd)) > > - Oleg > > On 5.10.2021 19.12, Richard Eisenberg wrote: > > I think the real difference is whether new type variables are brought into > scope. It seems that GHC can't deal with a proc-pattern-match that > introduces type variables, but it *can* deal with introduced constraints. I > have no idea *why* this is the case, but it seems a plausible (if > accidental) resting place for the implementation. > > Richard > > On Oct 3, 2021, at 12:19 PM, Alexis King wrote: > > Hi, > > I’ve been working on bringing my reimplementation of arrow notation back > up to date, and I’ve run into some confusion about the extent to which > arrow notation is “supposed” to support matching on GADT constructors. Note > [Arrows and patterns] in GHC.Tc.Gen.Pat suggests they aren’t supposed to > be supported at all, which is what I would essentially expect. But issues > #17423 and #18950 > provide examples of > using GADT constructors in arrow notation, and there seems to be some > expectation that in fact they *ought* to be supported, and some > recently-added test cases verify that’s the case. > > But this is quite odd, because it means the arrows test suite now includes > test cases that verify both that this is supported *and* that it isn’t… > and all of them pass! Here’s my understanding of the status quo: > > - > > Matching on constructors that bind bona fide existential variables is > not allowed, and this is verified by the arrowfail004 test case, which > involves the following program: > > data T = forall a. T a > > panic :: (Arrow arrow) => arrow T T > panic = proc (T x) -> do returnA -< T x > > This program is rejected with the following error message: > > arrowfail004.hs:12:15: > Proc patterns cannot use existential or GADT data constructors > In the pattern: T x > > - > > Despite the previous point, matching on constructors that bind > evidence is allowed. This is enshrined in test cases T15175, T17423, > and T18950, which match on constructors like these: > > data DecoType a where > DecoBool :: Maybe (String, String) -> Maybe (Int, Int) -> DecoType Bool > data Point a where > Point :: RealFloat a => a -> Point a > > > This seems rather contradictory to me. I don’t think there’s much of a > meaningful distinction between these types of matches, as they create > precisely the same set of challenges from the Core point of view… right? > And even if I’m wrong, the error message in arrowfail004 seems rather > misleading, since I would definitely call DecoBool and Point above “GADT > data constructors”. > > So what’s the intended story here? Is matching on GADT constructors in > arrow notation supposed to be allowed or not? (I suspect this is really > just yet another case of “nobody really knows what’s ‘supposed’ to happen > with arrow notation,” but I figured I might as well ask out of hopefulness > that someone has some idea.) > > Thanks, > Alexis > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Wed Oct 6 02:07:08 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Wed, 6 Oct 2021 02:07:08 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Message-ID: PUBLIC PUBLIC Hi, Thanks! Originally I was going to reply to this saying that my transformation isn't running in CoreM so where do I get that environment from, but then I realized I can just build it from the md_insts field of ModDetails. However, after thinking more about it, I also realized that I shouldn't ever really need to conjure up dictionaries from thin air: the whole reason I am making a specific specialization of an overloaded function is because I found somewhere a call at that type. But then, that call also gives me the dictionary! Of course at this point, this sounds exactly like what GHC already does in `specProgram`. So maybe I should be able to just use that? Unfortunately, my initial testing seems to show that even if I run `specBind` manually on my whole-program collected CoreProgram, it doesn't do the work I would expect from it! In the following example, I have only kept the definitions that are relevant. Before specialisation, I have the following whole-program Core: (>>=) :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] (>>=) = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> case v_sGm of { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> v_sGp } $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b [GblId, Arity=3, Unf=OtherCon []] $dm>> = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_sGQ [Occ=Once1] :: a -> m b [LclId] sat_sGQ = \ _ [Occ=Dead] -> mb } in >>= @m $dMonad @a @b ma sat_sGQ C:Monad [InlPrag=NOUSERINLINE CONLIKE] :: forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> Monad m [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] C:Monad = \ (@(m :: * -> *)) (eta_B0 [Occ=Once1] :: Applicative m) (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> C:Monad @m eta_B0 eta_B1 eta_B2 $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO [GblId[DFunId]] $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; $fMonadIO_$c>> [Occ=LoopBreaker] :: forall a b. IO a -> IO b -> IO b [GblId] $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; sat_sHr :: IO () [LclId] sat_sHr = returnIO @() () sat_sHq :: IO () [LclId] sat_sHq = returnIO @() () main :: IO () [GblId] main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr Now I pass this to GHC's `specBind`, but the output is exactly the same as the input! (or it's close enough that I can't spot the difference). (>>=) :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] (>>=) = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> case v_sGm of { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> v_sGp } $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b [GblId, Arity=3, Unf=OtherCon []] $dm>> = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_MHt [Occ=Once1] :: a -> m b [LclId] sat_MHt = \ _ [Occ=Dead] -> mb } in >>= @m $dMonad @a @b ma sat_MHt C:Monad [InlPrag=NOUSERINLINE CONLIKE] :: forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> Monad m [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] C:Monad = \ (@(m :: * -> *)) (eta_B0 [Occ=Once1] :: Applicative m) (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> C:Monad @m eta_B0 eta_B1 eta_B2 $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO [GblId[DFunId]] $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; $fMonadIO_$c>> [Occ=LoopBreaker] :: forall a b. IO a -> IO b -> IO b [GblId] $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; sat_sHr :: IO () [LclId] sat_sHr = returnIO @() () sat_sHq :: IO () [LclId] sat_sHq = returnIO @() () main :: IO () [GblId] main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr Why is that? I would have expected that the call chain main >-> $fMonadIO_$c>> >-> $dm>> would have resulted in a specialization along the lines of: $dm>>_IO :: forall a b. IO a -> IO b -> IO b >>=_IO :: forall a b. IO a -> (a -> IO b) -> IO b With appropriate definitions that can then be simplified away. But none of this seems to happen -- $dm>> doesn't get an IO-specific version, and so $fMonadIO_$c>> still ends up with a dictionary-passing call to $dm>>. Isn't this exactly the situation that the specialiser is supposed to eliminate? Thanks, Gergo From: Simon Peyton Jones Sent: Monday, October 4, 2021 7:29 PM To: Erdi, Gergo Cc: Montelatici, Raphael Laurent ; GHC Subject: [External] RE: Instantiation of overloaded definition *in Core* PUBLIC You can look it up in the class instance environment, which the Simplifier does have access to it. That's relatively easy when you have a simple dictionary like (Monad IO). But if you want (Eq [Int]) you first of all have to look up the (Eq [a]) dictionary, then the Eq Int dictionary, and apply the former to the latter. We don't (yet) have a simple API to do that, although it would not be hard to create one. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 04 October 2021 10:30 To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: Instantiation of overloaded definition *in Core* PUBLIC Hi, I'd like to instantiate Core definitions. For example, suppose I have the following Core definition: foo :: forall m a b. Monad m => m a -> m b -> m b foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... Now let's say I'd like to instantiate it for m ~ IO. It is quite straightforward to go from the above to: foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ... However, I would like to go all the way to: foo_IO :: forall a b. IO a -> IO b -> IO b foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ... Because instances are coherent, it should be sound to replace all occurrences of $d with "the" dictionary for Monad IO. However, the places I've found for this kind of query seem to live in the typechecker. How do I access this information while working with Core? Thanks, Gergo This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Wed Oct 6 08:24:06 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 6 Oct 2021 09:24:06 +0100 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: I think you need to run at least one simplifier pass as the specialisations are applied via rules (created by specProgram). On Wed, Oct 6, 2021 at 3:10 AM Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > > PUBLIC > > > > Hi, > > > > Thanks! Originally I was going to reply to this saying that my transformation isn’t running in CoreM so where do I get that environment from, but then I realized I can just build it from the md_insts field of ModDetails. However, after thinking more about it, I also realized that I shouldn’t ever really need to conjure up dictionaries from thin air: the whole reason I am making a specific specialization of an overloaded function is because I found somewhere a call at that type. But then, that call also gives me the dictionary! > > > > Of course at this point, this sounds exactly like what GHC already does in `specProgram`. So maybe I should be able to just use that? > > > > Unfortunately, my initial testing seems to show that even if I run `specBind` manually on my whole-program collected CoreProgram, it doesn’t do the work I would expect from it! > > > > In the following example, I have only kept the definitions that are relevant. Before specialisation, I have the following whole-program Core: > > > > (>>=) > > :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b > > [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] > > (>>=) > > = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> > > case v_sGm of > > { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> > > v_sGp > > } > > $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b > > [GblId, Arity=3, Unf=OtherCon []] > > $dm>> > > = \ (@(m :: * -> *)) > > ($dMonad [Occ=Once1] :: Monad m) > > (@a) > > (@b) > > (ma [Occ=Once1] :: m a) > > (mb [Occ=OnceL1] :: m b) -> > > let { > > sat_sGQ [Occ=Once1] :: a -> m b > > [LclId] > > sat_sGQ = \ _ [Occ=Dead] -> mb } in > > >>= @m $dMonad @a @b ma sat_sGQ > > C:Monad [InlPrag=NOUSERINLINE CONLIKE] > > :: forall (m :: * -> *). > > Applicative m > > -> (forall a b. m a -> (a -> m b) -> m b) > > -> (forall a b. m a -> m b -> m b) > > -> Monad m > > [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] > > C:Monad > > = \ (@(m :: * -> *)) > > (eta_B0 [Occ=Once1] :: Applicative m) > > (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) > > (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> > > C:Monad @m eta_B0 eta_B1 eta_B2 > > $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO > > [GblId[DFunId]] > > $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; > > $fMonadIO_$c>> [Occ=LoopBreaker] > > :: forall a b. IO a -> IO b -> IO b > > [GblId] > > $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; > > sat_sHr :: IO () > > [LclId] > > sat_sHr = returnIO @() () > > sat_sHq :: IO () > > [LclId] > > sat_sHq = returnIO @() () > > main :: IO () > > [GblId] > > main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr > > > > > > Now I pass this to GHC’s `specBind`, but the output is exactly the same as the input! (or it’s close enough that I can’t spot the difference). > > > > (>>=) > > :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b > > [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] > > (>>=) > > = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> > > case v_sGm of > > { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> > > v_sGp > > } > > $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b > > [GblId, Arity=3, Unf=OtherCon []] > > $dm>> > > = \ (@(m :: * -> *)) > > ($dMonad [Occ=Once1] :: Monad m) > > (@a) > > (@b) > > (ma [Occ=Once1] :: m a) > > (mb [Occ=OnceL1] :: m b) -> > > let { > > sat_MHt [Occ=Once1] :: a -> m b > > [LclId] > > sat_MHt = \ _ [Occ=Dead] -> mb } in > > >>= @m $dMonad @a @b ma sat_MHt > > C:Monad [InlPrag=NOUSERINLINE CONLIKE] > > :: forall (m :: * -> *). > > Applicative m > > -> (forall a b. m a -> (a -> m b) -> m b) > > -> (forall a b. m a -> m b -> m b) > > -> Monad m > > [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] > > C:Monad > > = \ (@(m :: * -> *)) > > (eta_B0 [Occ=Once1] :: Applicative m) > > (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) > > (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> > > C:Monad @m eta_B0 eta_B1 eta_B2 > > $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO > > [GblId[DFunId]] > > $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; > > $fMonadIO_$c>> [Occ=LoopBreaker] > > :: forall a b. IO a -> IO b -> IO b > > [GblId] > > $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; > > sat_sHr :: IO () > > [LclId] > > sat_sHr = returnIO @() () > > sat_sHq :: IO () > > [LclId] > > sat_sHq = returnIO @() () > > main :: IO () > > [GblId] > > main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr > > > > > > Why is that? I would have expected that the call chain main >-> $fMonadIO_$c>> >-> $dm>> would have resulted in a specialization along the lines of: > > > > $dm>>_IO :: forall a b. IO a -> IO b -> IO b > > >>=_IO :: forall a b. IO a -> (a -> IO b) -> IO b > > > > With appropriate definitions that can then be simplified away. > > > > But none of this seems to happen -- $dm>> doesn’t get an IO-specific version, and so $fMonadIO_$c>> still ends up with a dictionary-passing call to $dm>>. Isn’t this exactly the situation that the specialiser is supposed to eliminate? > > > > Thanks, > > Gergo > > > > From: Simon Peyton Jones > Sent: Monday, October 4, 2021 7:29 PM > To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent ; GHC > Subject: [External] RE: Instantiation of overloaded definition *in Core* > > > > PUBLIC > > You can look it up in the class instance environment, which the Simplifier does have access to it. That’s relatively easy when you have a simple dictionary like (Monad IO). But if you want (Eq [Int]) you first of all have to look up the (Eq [a]) dictionary, then the Eq Int dictionary, and apply the former to the latter. We don’t (yet) have a simple API to do that, although it would not be hard to create one. > > > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs > Sent: 04 October 2021 10:30 > To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: Instantiation of overloaded definition *in Core* > > > > PUBLIC > > > > Hi, > > > > I’d like to instantiate Core definitions. For example, suppose I have the following Core definition: > > > > foo :: forall m a b. Monad m => m a -> m b -> m b > > foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... > > > > Now let’s say I’d like to instantiate it for m ~ IO. It is quite straightforward to go from the above to: > > > > foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b > > foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ... > > > > However, I would like to go all the way to: > > > > foo_IO :: forall a b. IO a -> IO b -> IO b > > foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ... > > > > Because instances are coherent, it should be sound to replace all occurrences of $d with “the” dictionary for Monad IO. However, the places I’ve found for this kind of query seem to live in the typechecker. How do I access this information while working with Core? > > > > Thanks, > > Gergo > > > This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations > > Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm > > Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. > > Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. > > Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. > > Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From Gergo.Erdi at sc.com Wed Oct 6 08:52:48 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Wed, 6 Oct 2021 08:52:48 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Message-ID: INTERNAL I see. That will be a bit more involved to try out, because I don't have a ModGuts at hand -- I only have the ModDetails, and the collected CoreProgram from the whole program. But it seems `specProgram` only really uses the rules and the binds from the `ModGuts`, so I should be all right. But one thing I can easily try is just printing the UsageDetails as returned by the specBinds part of specProgram, and that seems empty. So if the actual work of specProgram happens by generating rules in specImports, how will specImports know what rules to generate, from an empty UsageDetails? -----Original Message----- From: Matthew Pickering Sent: Wednesday, October 6, 2021 4:24 PM To: Erdi, Gergo Cc: Simon Peyton Jones ; Montelatici, Raphael Laurent ; GHC Subject: [External] Re: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) I think you need to run at least one simplifier pass as the specialisations are applied via rules (created by specProgram). This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. From simonpj at microsoft.com Wed Oct 6 10:11:55 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 6 Oct 2021 10:11:55 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 06 October 2021 03:07 To: Simon Peyton Jones Cc: Montelatici, Raphael Laurent ; GHC Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Hi, Thanks! Originally I was going to reply to this saying that my transformation isn't running in CoreM so where do I get that environment from, but then I realized I can just build it from the md_insts field of ModDetails. However, after thinking more about it, I also realized that I shouldn't ever really need to conjure up dictionaries from thin air: the whole reason I am making a specific specialization of an overloaded function is because I found somewhere a call at that type. But then, that call also gives me the dictionary! Of course at this point, this sounds exactly like what GHC already does in `specProgram`. So maybe I should be able to just use that? Unfortunately, my initial testing seems to show that even if I run `specBind` manually on my whole-program collected CoreProgram, it doesn't do the work I would expect from it! In the following example, I have only kept the definitions that are relevant. Before specialisation, I have the following whole-program Core: (>>=) :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] (>>=) = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> case v_sGm of { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> v_sGp } $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b [GblId, Arity=3, Unf=OtherCon []] $dm>> = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_sGQ [Occ=Once1] :: a -> m b [LclId] sat_sGQ = \ _ [Occ=Dead] -> mb } in >>= @m $dMonad @a @b ma sat_sGQ C:Monad [InlPrag=NOUSERINLINE CONLIKE] :: forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> Monad m [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] C:Monad = \ (@(m :: * -> *)) (eta_B0 [Occ=Once1] :: Applicative m) (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> C:Monad @m eta_B0 eta_B1 eta_B2 $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO [GblId[DFunId]] $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; $fMonadIO_$c>> [Occ=LoopBreaker] :: forall a b. IO a -> IO b -> IO b [GblId] $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; sat_sHr :: IO () [LclId] sat_sHr = returnIO @() () sat_sHq :: IO () [LclId] sat_sHq = returnIO @() () main :: IO () [GblId] main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr Now I pass this to GHC's `specBind`, but the output is exactly the same as the input! (or it's close enough that I can't spot the difference). (>>=) :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=] (>>=) = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) -> case v_sGm of { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] -> v_sGp } $dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b [GblId, Arity=3, Unf=OtherCon []] $dm>> = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_MHt [Occ=Once1] :: a -> m b [LclId] sat_MHt = \ _ [Occ=Dead] -> mb } in >>= @m $dMonad @a @b ma sat_MHt C:Monad [InlPrag=NOUSERINLINE CONLIKE] :: forall (m :: * -> *). Applicative m -> (forall a b. m a -> (a -> m b) -> m b) -> (forall a b. m a -> m b -> m b) -> Monad m [GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []] C:Monad = \ (@(m :: * -> *)) (eta_B0 [Occ=Once1] :: Applicative m) (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b) (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) -> C:Monad @m eta_B0 eta_B1 eta_B2 $fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO [GblId[DFunId]] $fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>; $fMonadIO_$c>> [Occ=LoopBreaker] :: forall a b. IO a -> IO b -> IO b [GblId] $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b; sat_sHr :: IO () [LclId] sat_sHr = returnIO @() () sat_sHq :: IO () [LclId] sat_sHq = returnIO @() () main :: IO () [GblId] main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr Why is that? I would have expected that the call chain main >-> $fMonadIO_$c>> >-> $dm>> would have resulted in a specialization along the lines of: $dm>>_IO :: forall a b. IO a -> IO b -> IO b >>=_IO :: forall a b. IO a -> (a -> IO b) -> IO b With appropriate definitions that can then be simplified away. But none of this seems to happen -- $dm>> doesn't get an IO-specific version, and so $fMonadIO_$c>> still ends up with a dictionary-passing call to $dm>>. Isn't this exactly the situation that the specialiser is supposed to eliminate? Thanks, Gergo From: Simon Peyton Jones > Sent: Monday, October 4, 2021 7:29 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Instantiation of overloaded definition *in Core* PUBLIC You can look it up in the class instance environment, which the Simplifier does have access to it. That's relatively easy when you have a simple dictionary like (Monad IO). But if you want (Eq [Int]) you first of all have to look up the (Eq [a]) dictionary, then the Eq Int dictionary, and apply the former to the latter. We don't (yet) have a simple API to do that, although it would not be hard to create one. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 04 October 2021 10:30 To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: Instantiation of overloaded definition *in Core* PUBLIC Hi, I'd like to instantiate Core definitions. For example, suppose I have the following Core definition: foo :: forall m a b. Monad m => m a -> m b -> m b foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... Now let's say I'd like to instantiate it for m ~ IO. It is quite straightforward to go from the above to: foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ... However, I would like to go all the way to: foo_IO :: forall a b. IO a -> IO b -> IO b foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ... Because instances are coherent, it should be sound to replace all occurrences of $d with "the" dictionary for Monad IO. However, the places I've found for this kind of query seem to live in the typechecker. How do I access this information while working with Core? Thanks, Gergo This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Thu Oct 7 01:30:10 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Thu, 7 Oct 2021 01:30:10 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo Cc: Montelatici, Raphael Laurent ; GHC Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From klebinger.andreas at gmx.at Thu Oct 7 13:43:39 2021 From: klebinger.andreas at gmx.at (Andreas Klebinger) Date: Thu, 7 Oct 2021 15:43:39 +0200 Subject: Perf backtrace support. Message-ID: <6e678d57-f51d-8019-f93a-dc732aa09e7e@gmx.at> Hello Devs, as some of you know I've recently been working on #8272. The goal being to use the machine stack register for the STG stack as a means to get perf backtraces. I've succeeded in making a branch that works for the first part but have so far been unable to get perf to generate proper back traces. For various reasons I will stop looking at that particular issue. So if anyone feels interested in figuring out where the interaction between our dwarf info and perf unwinding the stack goes wrong please take a look! There is more information on the ticket. Cheers Andreas -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Thu Oct 7 17:35:57 2021 From: ben at well-typed.com (Ben Gamari) Date: Thu, 07 Oct 2021 13:35:57 -0400 Subject: Temporary Outage Message-ID: <87y274ivpz.fsf@smart-cactus.org> Hi all, You may notice that currently there are numerous CI failures due to apparent network issues. This appears to be due to a network outage on the part of our hosting providing. Further updates are available from Packet [1]. Hopefully the issue will be resolved within the next few hours. Cheers, - Ben [1] https://status.equinixmetal.com/ -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 487 bytes Desc: not available URL: From clintonmead at gmail.com Thu Oct 7 23:36:41 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Fri, 8 Oct 2021 10:36:41 +1100 Subject: Why can't arguments be levity polymorphic for inline functions? Message-ID: Hi All Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy enough to put it here. Section 6.4.12.1 of the GHC user manual points out, if we allowed levity polymorphic arguments, then we would have no way to compile these functions, because the code required for different levites is different. However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's no need to compile it as it's full definition is in the interface file. Callers can just compile it themselves with the levity they require. Indeed callers of inline functions already compile their own versions even without levity polymorphism (for example, presumably inlining function calls that are known at compile time). The only sticking point to this that I could find was that GHC will only inline the function if it is fully applied , which suggests that the possibility of partial application means we can't inline and hence need a compiled version of the code. But this seems like a silly restriction, as we have the full RHS of the definition in the interface file. The caller can easily create and compile it's own partially applied version. It should be able to do this regardless of levity. It seems to me we're okay as long as the following three things aren't true simultaneously: 1. Blah has levity polymorphic arguments 2. Blah is exported 3. Blah is not inline If a function "Blah" is not exported, we shouldn't care about levity polymorphic arguments, because we have it's RHS on hand in the current module and compile it as appropriate. And if it's inline, we're exposing it's full RHS to other callers so we're still fine also. Only when these three conditions combine should we give an error, say like: "Blah has levity polymorphic arguments, is exported, and is not inline. Please either remove levity polymorphic arguments, not export it or add an {-# INLINE #-} or {-# INLINABLE #-} pragma. I presume however there are some added complications that I don't understand, and I'm very interested in what they are as I presume they'll be quite interesting. Thanks, Clinton -------------- next part -------------- An HTML attachment was scrubbed... URL: From klebinger.andreas at gmx.at Fri Oct 8 12:39:00 2021 From: klebinger.andreas at gmx.at (Andreas Klebinger) Date: Fri, 8 Oct 2021 14:39:00 +0200 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: Message-ID: <0d28319c-c4e9-2d13-6a4a-acc06ee0e563@gmx.at> Hey Clinton, I think the state of things is best summarised it's in principle possible to implement. But it's unclear how best to do so or even if it's worth having this feature at all. The biggest issue being code bloat. As you say a caller could create it's own version of the function with the right kind of argument type. But that means duplicating the function for every use site (although some might be able to be commoned up). Potentially causing a lot of code bloat and compile time overhead. In a similar fashion we could create each potential version we need from the get go to avoid duplicating the same function. But that runs the risk of generating far more code than what is actually used. Last but not least GHC currently doesn't always load unfoldings. In particular if you compile a module with optimizations disabled the RHS is currently *not* available to the compiler when looking at the use site. There already is a mechanism to bypass this in GHC where a function *must* be inlined (compulsory unfoldings). But it's currently reserved for built in functions. We could just make INLINE bindings compulsory if they have levity-polymorphic arguments sure. But again it's not clear this is really desireable. I don't think this has to mean we couldn't change how things work to accomodate levity-polymorphic arguments. It just seems it's unclear what a good design would look like and if it's worth having. Cheers Andreas Am 08/10/2021 um 01:36 schrieb Clinton Mead: > Hi All > > Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy > enough to put it here. > > Section 6.4.12.1 > > of the GHC user manual points out, if we allowed levity polymorphic > arguments, then we would have no way to compile these functions, > because the code required for different levites is different. > > However, if such a function is {-# INLINE #-} or{-# INLINABLE #-} > there's no need to compile it as it's full definition is in the > interface file. Callers can just compile it themselves with the levity > they require. Indeed callers of inline functions already compile their > own versions even without levity polymorphism (for example, presumably > inlining function calls that are known at compile time). > > The only sticking point to this that I could find was that GHC will > only inline the function if it is fully applied > , > which suggests that the possibility of partial application means we > can't inline and hence need a compiled version of the code. But this > seems like a silly restriction, as we have the full RHS of the > definition in the interface file. The caller can easily create and > compile it's own partially applied version. It should be able to do > this regardless of levity. > > It seems to me we're okay as long as the following three things aren't > true simultaneously: > > 1. Blah has levity polymorphic arguments > 2. Blah is exported > 3. Blah is not inline > > If a function "Blah" is not exported, we shouldn't care about levity > polymorphic arguments, because we have it's RHS on hand in the current > module and compile it as appropriate. And if it's inline, we're > exposing it's full RHS to other callers so we're still fine also. Only > when these three conditions combine should we give an error, say like: > > "Blah has levity polymorphic arguments, is exported, and is not > inline. Please either remove levity polymorphic arguments, not export > it or add an {-# INLINE #-} or {-# INLINABLE #-} pragma. > > I presume however there are some added complications that I don't > understand, and I'm very interested in what they are as I presume > they'll be quite interesting. > > Thanks, > Clinton > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From clintonmead at gmail.com Fri Oct 8 14:30:51 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Sat, 9 Oct 2021 01:30:51 +1100 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: <0d28319c-c4e9-2d13-6a4a-acc06ee0e563@gmx.at> References: <0d28319c-c4e9-2d13-6a4a-acc06ee0e563@gmx.at> Message-ID: Thanks for your reply Andreas. Just some further thoughts, perhaps we don't even require inline. Correct me if I'm wrong, but couldn't we compile even functions with levity polymorphic arguments by just boxing all the arguments? This would also mean the caller would have to box arguments before passing. You'd also need to box any working variables inside the function with levity other than `Type`. This to a certain extent defeats the purpose of levity polymorphism when it's intended as an optimisation to avoid boxed types, but it does give a fallback we can always use. Yes, if you inline you can get code bloat. But that's a risk when you inline any function. Cheers, Clinton On Fri, Oct 8, 2021 at 11:39 PM Andreas Klebinger wrote: > Hey Clinton, > > I think the state of things is best summarised it's in principle possible > to implement. But it's unclear how best to do so > or even if it's worth having this feature at all. > > The biggest issue being code bloat. > > As you say a caller could create it's own version of the function with the > right kind of argument type. > But that means duplicating the function for every use site (although some > might be able to be commoned up). Potentially causing a lot of code > bloat and compile time overhead. > > In a similar fashion we could create each potential version we need from > the get go to avoid duplicating the same function. > But that runs the risk of generating far more code than what is actually > used. > > Last but not least GHC currently doesn't always load unfoldings. In > particular if you compile a module with optimizations disabled the RHS is > currently *not* > available to the compiler when looking at the use site. There already is a > mechanism to bypass this in GHC where a function *must* be inlined > (compulsory unfoldings). > But it's currently reserved for built in functions. We could just make > INLINE bindings compulsory if they have levity-polymorphic arguments sure. > But again it's not clear > this is really desireable. > > I don't think this has to mean we couldn't change how things work to > accomodate levity-polymorphic arguments. It just seems it's unclear what a > good design > would look like and if it's worth having. > > Cheers > Andreas > Am 08/10/2021 um 01:36 schrieb Clinton Mead: > > Hi All > > Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy > enough to put it here. > > Section 6.4.12.1 > > of the GHC user manual points out, if we allowed levity polymorphic > arguments, then we would have no way to compile these functions, because > the code required for different levites is different. > > However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} > there's no need to compile it as it's full definition is in the interface > file. Callers can just compile it themselves with the levity they require. > Indeed callers of inline functions already compile their own versions even > without levity polymorphism (for example, presumably inlining function > calls that are known at compile time). > > The only sticking point to this that I could find was that GHC will only > inline the function if it is fully applied > , > which suggests that the possibility of partial application means we can't > inline and hence need a compiled version of the code. But this seems like a > silly restriction, as we have the full RHS of the definition in the > interface file. The caller can easily create and compile it's own partially > applied version. It should be able to do this regardless of levity. > > It seems to me we're okay as long as the following three things aren't > true simultaneously: > > 1. Blah has levity polymorphic arguments > 2. Blah is exported > 3. Blah is not inline > > If a function "Blah" is not exported, we shouldn't care about levity > polymorphic arguments, because we have it's RHS on hand in the current > module and compile it as appropriate. And if it's inline, we're exposing > it's full RHS to other callers so we're still fine also. Only when these > three conditions combine should we give an error, say like: > > "Blah has levity polymorphic arguments, is exported, and is not inline. > Please either remove levity polymorphic arguments, not export it or add an {-# > INLINE #-} or {-# INLINABLE #-} pragma. > > I presume however there are some added complications that I don't > understand, and I'm very interested in what they are as I presume they'll > be quite interesting. > > Thanks, > Clinton > > > _______________________________________________ > ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Fri Oct 8 14:46:02 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Fri, 8 Oct 2021 14:46:02 +0000 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: Message-ID: <010f017c605e4373-da048ef3-10b6-42de-90f1-fba29456218a-000000@us-east-2.amazonses.com> One significant problem is that {-# INLINE #-} functions are not actually always inlined! Specifically, if an inline-function is not passed all of its arguments, it will not be inlined. This poses a problem for levity-polymorphic functions, and GHC already does some special handling of the few levity-polymorphic primitives, in case they are ever used without all of their arguments. As for boxing levity-polymorphic arguments: that's plausible, but then I think you've defeated the programmer's intended aim. The solution to me is some kind of so-called template polymorphism . This might work, but it would take a fair amount of design work first. Richard > On Oct 7, 2021, at 7:36 PM, Clinton Mead wrote: > > Hi All > > Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy enough to put it here. > > Section 6.4.12.1 of the GHC user manual points out, if we allowed levity polymorphic arguments, then we would have no way to compile these functions, because the code required for different levites is different. > > However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's no need to compile it as it's full definition is in the interface file. Callers can just compile it themselves with the levity they require. Indeed callers of inline functions already compile their own versions even without levity polymorphism (for example, presumably inlining function calls that are known at compile time). > > The only sticking point to this that I could find was that GHC will only inline the function if it is fully applied , which suggests that the possibility of partial application means we can't inline and hence need a compiled version of the code. But this seems like a silly restriction, as we have the full RHS of the definition in the interface file. The caller can easily create and compile it's own partially applied version. It should be able to do this regardless of levity. > > It seems to me we're okay as long as the following three things aren't true simultaneously: > > 1. Blah has levity polymorphic arguments > 2. Blah is exported > 3. Blah is not inline > > If a function "Blah" is not exported, we shouldn't care about levity polymorphic arguments, because we have it's RHS on hand in the current module and compile it as appropriate. And if it's inline, we're exposing it's full RHS to other callers so we're still fine also. Only when these three conditions combine should we give an error, say like: > > "Blah has levity polymorphic arguments, is exported, and is not inline. Please either remove levity polymorphic arguments, not export it or add an {-# INLINE #-} or {-# INLINABLE #-} pragma. > > I presume however there are some added complications that I don't understand, and I'm very interested in what they are as I presume they'll be quite interesting. > > Thanks, > Clinton > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Fri Oct 8 14:51:28 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 08 Oct 2021 10:51:28 -0400 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: Message-ID: <87k0inin97.fsf@smart-cactus.org> Clinton Mead writes: > Hi All > > Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy > enough to put it here. > > Section 6.4.12.1 > > of the GHC user manual points out, if we allowed levity polymorphic > arguments, then we would have no way to compile these functions, because > the code required for different levites is different. > > However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's > no need to compile it as it's full definition is in the interface file. > Callers can just compile it themselves with the levity they require. Indeed > callers of inline functions already compile their own versions even without > levity polymorphism (for example, presumably inlining function calls that > are known at compile time). > > The only sticking point to this that I could find was that GHC will only > inline the function if it is fully applied > , > which suggests that the possibility of partial application means we can't > inline and hence need a compiled version of the code. But this seems like a > silly restriction, as we have the full RHS of the definition in the > interface file. The caller can easily create and compile it's own partially > applied version. It should be able to do this regardless of levity. > > It seems to me we're okay as long as the following three things aren't true > simultaneously: > > 1. Blah has levity polymorphic arguments > 2. Blah is exported > 3. Blah is not inline > In my mind the fundamental problem with this approach is that it means that a program's acceptance by the compiler hinges upon pragmas. This is a rather significant departure from the status quo, where one can remove all pragmas and still end up with a well-formed program. In this sense, pragmas aren't really part of the Haskell language but are rather bits of interesting metadata that the compiler may or may not pay heed to. Given that levity polymorphic functions have rather deep implications on compilation strategy, I suspect that the cleanest path to allowing it would be to further extend the type system (for instance, with a new "macro expanding" arrow notion). 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 cdsmith at gmail.com Fri Oct 8 14:54:32 2021 From: cdsmith at gmail.com (Chris Smith) Date: Fri, 8 Oct 2021 10:54:32 -0400 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: <87k0inin97.fsf@smart-cactus.org> References: <87k0inin97.fsf@smart-cactus.org> Message-ID: On Fri, Oct 8, 2021 at 10:51 AM Ben Gamari wrote: > In my mind the fundamental problem with this approach is that it means > that a program's acceptance by the compiler hinges upon pragmas. > This is a rather significant departure from the status quo, where one > can remove all pragmas and still end up with a well-formed program. > In this sense, pragmas aren't really part of the Haskell language but > are rather bits of interesting metadata that the compiler may or may not > pay heed to. > I don't believe this is really the status quo. In particular, the pragmas relating to overlapping instances definitely do affect whether a program type-checks or not. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Fri Oct 8 15:02:36 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Fri, 8 Oct 2021 15:02:36 +0000 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: <87k0inin97.fsf@smart-cactus.org> References: <87k0inin97.fsf@smart-cactus.org> Message-ID: <010f017c606d6c7c-94e208c2-97b9-4a10-807b-3b51a21d47d5-000000@us-east-2.amazonses.com> > On Oct 8, 2021, at 10:51 AM, Ben Gamari wrote: > In my mind the fundamental problem with this approach is that it means > that a program's acceptance by the compiler hinges upon pragmas. I think being able to ignore pragmas is a worthy goal, but one we're rather far short of, at the moment: overlapping pragmas (as Chris has pointed out), language pragmas (!), options pragmas setting -Werror, plugin pragmas, maybe others. Richard From ben at smart-cactus.org Fri Oct 8 15:06:18 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 08 Oct 2021 11:06:18 -0400 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: <87k0inin97.fsf@smart-cactus.org> Message-ID: <87h7drimjs.fsf@smart-cactus.org> Chris Smith writes: > On Fri, Oct 8, 2021 at 10:51 AM Ben Gamari wrote: > >> In my mind the fundamental problem with this approach is that it means >> that a program's acceptance by the compiler hinges upon pragmas. >> This is a rather significant departure from the status quo, where one >> can remove all pragmas and still end up with a well-formed program. >> In this sense, pragmas aren't really part of the Haskell language but >> are rather bits of interesting metadata that the compiler may or may not >> pay heed to. >> > > I don't believe this is really the status quo. In particular, the pragmas > relating to overlapping instances definitely do affect whether a program > type-checks or not. Yes, this is a fair point. Moreover, the same can be said of LANGUAGE pragmas more generally. I will rephrase my statement to reflect what was in my head when I initially wrote it: >> In my mind the fundamental problem with this approach is that it means >> that a program's acceptance by the compiler hinges upon INLINE pragmas. >> This is a rather significant departure from the status quo, where one >> can remove all INLINE, INLINEABLE, RULES, and SPECIALISE pragmas and >> still end up with a well-formed program. These pragmas all share the property that they don't change program semantics but rather merely affect operational behavior. Consequently, they should not change whether a program should be accepted. 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 simonpj at microsoft.com Fri Oct 8 15:17:33 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 8 Oct 2021 15:17:33 +0000 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: Message-ID: We do have a few such functions, and we give them a "compulsory unfolding" which means they MUST be inlined at EVERY call site. But * Usually if a module exports a function, it generates code for that function. But for these guys it can't. We don't have a mechanism for *not* generating code for user-defined functions. We could add an INLINE-COMPULSORY pragma perhaps. * Even then we'd have to check that every call of such a function is applied to enough arguments to get rid of all levity/representation polymorphism; so that when it is inlined all is good. It's not clear how to do that in general. That's the kind of thing Richard means by "templates". Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs On Behalf Of Clinton Mead Sent: 08 October 2021 00:37 To: ghc-devs at haskell.org Subject: Why can't arguments be levity polymorphic for inline functions? Hi All Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy enough to put it here. Section 6.4.12.1 of the GHC user manual points out, if we allowed levity polymorphic arguments, then we would have no way to compile these functions, because the code required for different levites is different. However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's no need to compile it as it's full definition is in the interface file. Callers can just compile it themselves with the levity they require. Indeed callers of inline functions already compile their own versions even without levity polymorphism (for example, presumably inlining function calls that are known at compile time). The only sticking point to this that I could find was that GHC will only inline the function if it is fully applied, which suggests that the possibility of partial application means we can't inline and hence need a compiled version of the code. But this seems like a silly restriction, as we have the full RHS of the definition in the interface file. The caller can easily create and compile it's own partially applied version. It should be able to do this regardless of levity. It seems to me we're okay as long as the following three things aren't true simultaneously: 1. Blah has levity polymorphic arguments 2. Blah is exported 3. Blah is not inline If a function "Blah" is not exported, we shouldn't care about levity polymorphic arguments, because we have it's RHS on hand in the current module and compile it as appropriate. And if it's inline, we're exposing it's full RHS to other callers so we're still fine also. Only when these three conditions combine should we give an error, say like: "Blah has levity polymorphic arguments, is exported, and is not inline. Please either remove levity polymorphic arguments, not export it or add an {-# INLINE #-} or {-# INLINABLE #-} pragma. I presume however there are some added complications that I don't understand, and I'm very interested in what they are as I presume they'll be quite interesting. Thanks, Clinton -------------- next part -------------- An HTML attachment was scrubbed... URL: From krz.gogolewski at gmail.com Fri Oct 8 15:50:38 2021 From: krz.gogolewski at gmail.com (Krzysztof Gogolewski) Date: Fri, 8 Oct 2021 17:50:38 +0200 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: References: Message-ID: Note that you can use Typed Template Haskell as a workaround, e.g. f :: forall r (a :: TYPE r). Code Q (a -> a) f = [||\x -> x||] In the future this might be integrated better with the restriction polymorphism checking: https://gitlab.haskell.org/ghc/ghc/-/issues/18170 https://gitlab.haskell.org/ghc/ghc/-/wikis/FixedRuntimeRep#typed-template-haskell On Fri, Oct 8, 2021 at 5:19 PM Simon Peyton Jones via ghc-devs wrote: > > We do have a few such functions, and we give them a “compulsory unfolding” which means they MUST be inlined at EVERY call site. But > > > > Usually if a module exports a function, it generates code for that function. But for these guys it can’t. We don’t have a mechanism for *not* generating code for user-defined functions. We could add an INLINE-COMPULSORY pragma perhaps. > Even then we’d have to check that every call of such a function is applied to enough arguments to get rid of all levity/representation polymorphism; so that when it is inlined all is good. It’s not clear how to do that in general. > > > > That’s the kind of thing Richard means by “templates”. > > > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: ghc-devs On Behalf Of Clinton Mead > Sent: 08 October 2021 00:37 > To: ghc-devs at haskell.org > Subject: Why can't arguments be levity polymorphic for inline functions? > > > > Hi All > > > > Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy enough to put it here. > > > > Section 6.4.12.1 of the GHC user manual points out, if we allowed levity polymorphic arguments, then we would have no way to compile these functions, because the code required for different levites is different. > > > > However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's no need to compile it as it's full definition is in the interface file. Callers can just compile it themselves with the levity they require. Indeed callers of inline functions already compile their own versions even without levity polymorphism (for example, presumably inlining function calls that are known at compile time). > > > > The only sticking point to this that I could find was that GHC will only inline the function if it is fully applied, which suggests that the possibility of partial application means we can't inline and hence need a compiled version of the code. But this seems like a silly restriction, as we have the full RHS of the definition in the interface file. The caller can easily create and compile it's own partially applied version. It should be able to do this regardless of levity. > > > > It seems to me we're okay as long as the following three things aren't true simultaneously: > > > > 1. Blah has levity polymorphic arguments > > 2. Blah is exported > > 3. Blah is not inline > > > > If a function "Blah" is not exported, we shouldn't care about levity polymorphic arguments, because we have it's RHS on hand in the current module and compile it as appropriate. And if it's inline, we're exposing it's full RHS to other callers so we're still fine also. Only when these three conditions combine should we give an error, say like: > > > > "Blah has levity polymorphic arguments, is exported, and is not inline. Please either remove levity polymorphic arguments, not export it or add an {-# INLINE #-} or {-# INLINABLE #-} pragma. > > > > I presume however there are some added complications that I don't understand, and I'm very interested in what they are as I presume they'll be quite interesting. > > > > Thanks, > Clinton > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From clintonmead at gmail.com Fri Oct 8 16:38:59 2021 From: clintonmead at gmail.com (Clinton Mead) Date: Sat, 9 Oct 2021 03:38:59 +1100 Subject: Why can't arguments be levity polymorphic for inline functions? In-Reply-To: <87h7drimjs.fsf@smart-cactus.org> References: <87k0inin97.fsf@smart-cactus.org> <87h7drimjs.fsf@smart-cactus.org> Message-ID: Ben, The suggestion of erroring if the inline pragma was not there was just because I thought it would be better than silently doing something different. But that's just a subjective opinion, it's not core to what I'm proposing. Indeed there are two other options: 1. Make levity polymorphic functions implicitly inline OR 2. Compile a version which wraps all the levity polymorphism in boxes. Either approach would mean the program would still be accepted with or without the pragma. Whether either of them are a good idea is debatable, but it shows it's not necessary to require a pragma. So if it's important that excluding a pragma doesn't result in a program being rejected, either of the above options would solve that issue. On Sat, Oct 9, 2021 at 2:06 AM Ben Gamari wrote: > Chris Smith writes: > > > On Fri, Oct 8, 2021 at 10:51 AM Ben Gamari wrote: > > > >> In my mind the fundamental problem with this approach is that it means > >> that a program's acceptance by the compiler hinges upon pragmas. > >> This is a rather significant departure from the status quo, where one > >> can remove all pragmas and still end up with a well-formed program. > >> In this sense, pragmas aren't really part of the Haskell language but > >> are rather bits of interesting metadata that the compiler may or may not > >> pay heed to. > >> > > > > I don't believe this is really the status quo. In particular, the > pragmas > > relating to overlapping instances definitely do affect whether a program > > type-checks or not. > > Yes, this is a fair point. Moreover, the same can be said of > LANGUAGE pragmas more generally. I will rephrase my statement to reflect > what was in my head when I initially wrote it: > > >> In my mind the fundamental problem with this approach is that it means > >> that a program's acceptance by the compiler hinges upon INLINE pragmas. > >> This is a rather significant departure from the status quo, where one > >> can remove all INLINE, INLINEABLE, RULES, and SPECIALISE pragmas and > >> still end up with a well-formed program. > > These pragmas all share the property that they don't change program > semantics but rather merely affect operational behavior. Consequently, > they should not change whether a program should be accepted. > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 02:58:17 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 02:58:17 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to expose the first half of specProgram, i.e. the part that calls `go binds`. I did that because I want to apply specialisation on collected whole-program Core, not just whatever would be in scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't even have a ModGuts at hand. However, I found out from Matt's email on this thread that this is not going to be enough and eventually I'll need to figure out how I intend to apply the rewrite rules that come out of this. So for now, I am just turning on specialization in the normal pipeline by setting Opt_Specialise, Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not seeing $dm>> being specialized. Is this because I define each of "class Monad", "data IO a", "instance Monad IO", and "main", in four distinct modules? In other words, is this something I will not be able to try out until I figure out how to make a fake ModGuts and run a CoreM from outside the normal compilation pipeline, feeding it the whole-program collected CoreBinds? But if so, why is it that when I feed my whole program to just specBinds (which I can try easily since it has no ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get back an empty UsageDetails? Thanks, Gergo For reference, the relevant definitions dumped from GHC with specialization (supposedly) turned on: main = $fMonadIO_$c>> @() @() sat_sJg xmain $fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b $fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa; $dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b $dm>> = \ (@(m_ani :: Type -> Type)) ($dMonad_sIi [Occ=Once1] :: Monad m_ani) (@a_ar4) (@b_ar5) (ma_sIj [Occ=Once1] :: m_ani a_ar4) (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) -> let { sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5 [LclId] sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm From: Erdi, Gergo Sent: Thursday, October 7, 2021 9:30 AM To: Simon Peyton Jones Cc: Montelatici, Raphael Laurent ; GHC Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones > Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 04:08:38 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 04:08:38 +0000 Subject: -O* does more than what's in optLevelFlags? Message-ID: PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Oct 11 07:32:56 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 11 Oct 2021 07:32:56 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: It's incredibly hard to debug this sort of thing remotely, without the ability to reproduce it. First, you are using a variant of GHC, with changes that we can only guess at. Second, even with unmodified GHC I often find that unexpected things happen - until I dig deeper and it becomes obvious! There is one odd thing about your dump: it seems to be in reverse dependency order, with functions being defined before they are used, rather than after. That would certainly stop the specialiser from working. The occurrence analyser would sort this out (literally). But that's a total guess. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 11 October 2021 03:58 To: Simon Peyton Jones ; Matthew Pickering Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to expose the first half of specProgram, i.e. the part that calls `go binds`. I did that because I want to apply specialisation on collected whole-program Core, not just whatever would be in scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't even have a ModGuts at hand. However, I found out from Matt's email on this thread that this is not going to be enough and eventually I'll need to figure out how I intend to apply the rewrite rules that come out of this. So for now, I am just turning on specialization in the normal pipeline by setting Opt_Specialise, Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not seeing $dm>> being specialized. Is this because I define each of "class Monad", "data IO a", "instance Monad IO", and "main", in four distinct modules? In other words, is this something I will not be able to try out until I figure out how to make a fake ModGuts and run a CoreM from outside the normal compilation pipeline, feeding it the whole-program collected CoreBinds? But if so, why is it that when I feed my whole program to just specBinds (which I can try easily since it has no ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get back an empty UsageDetails? Thanks, Gergo For reference, the relevant definitions dumped from GHC with specialization (supposedly) turned on: main = $fMonadIO_$c>> @() @() sat_sJg xmain $fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b $fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa; $dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b $dm>> = \ (@(m_ani :: Type -> Type)) ($dMonad_sIi [Occ=Once1] :: Monad m_ani) (@a_ar4) (@b_ar5) (ma_sIj [Occ=Once1] :: m_ani a_ar4) (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) -> let { sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5 [LclId] sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm From: Erdi, Gergo Sent: Thursday, October 7, 2021 9:30 AM To: Simon Peyton Jones > Cc: Montelatici, Raphael Laurent >; GHC > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones > Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 07:54:21 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 07:54:21 +0000 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: PUBLIC I've done some digging into this, and it turns out the DynFlag's `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn't equal setting -On for the right "n"; in fact, currently setting most of these flags does NOTHING on its own unless -On with n>=1 is *also* passed on the command line, and there is no command line flag to *only* turn on Core optimizations in the abstract, without actually turning any specific ones on. Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? From: Erdi, Gergo Sent: Monday, October 11, 2021 12:09 PM To: 'GHC' Cc: Montelatici, Raphael Laurent Subject: -O* does more than what's in optLevelFlags? PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From sylvain at haskus.fr Mon Oct 11 07:56:30 2021 From: sylvain at haskus.fr (Sylvain Henry) Date: Mon, 11 Oct 2021 09:56:30 +0200 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: <00ffa342-0273-4706-00f6-684c675cf442@haskus.fr> Hi, Indeed the optimisation level is directly queried in a few places (e.g. grep "optLevel" and "opt_level"). Especially in Core opt pipeline getCoreToDo returns:     core_todo =      if opt_level == 0 then        [ static_ptrs_float_outwards,          CoreDoSimplify max_iter              (base_mode { sm_phase = FinalPhase                         , sm_names = ["Non-opt simplification"] })        , add_caller_ccs        ]      else {- opt_level >= 1 -} [...] Somewhat relevant issue: https://gitlab.haskell.org/ghc/ghc/-/issues/17844 On 11/10/2021 06:08, Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > > What is set by -O* that is not included in optLevelFlags? > > I would have thought that setting all the flags implied by, e.g., -O1, > would be the same as setting -O1 itself. But this is not the case! > Here are all the flags for O1 from optLevelFlags: > > Opt_DoLambdaEtaExpansion > > Opt_DoEtaReduction > > Opt_LlvmTBAA > > Opt_CallArity > > Opt_Exitification > > Opt_CaseMerge > > Opt_CaseFolding > > Opt_CmmElimCommonBlocks > > Opt_CmmSink > > Opt_CmmStaticPred > > Opt_CSE > > Opt_StgCSE > > Opt_EnableRewriteRules > > Opt_FloatIn > > Opt_FullLaziness > > Opt_IgnoreAsserts > > Opt_Loopification > > Opt_CfgBlocklayout > > Opt_Specialise > > Opt_CrossModuleSpecialise > > Opt_InlineGenerics > > Opt_Strictness > > Opt_UnboxSmallStrictFields > > Opt_CprAnal > > Opt_WorkerWrapper > > Opt_SolveConstantDicts > > Opt_NumConstantFolding > > And here are the ones that are set by O0 (the default) but not by O1: > > Opt_IgnoreInterfacePragmas > > Opt_OmitInterfacePragmas > > So I expected that the following two invocations of GHC would be > equivalent: > > 1. ghc -O1 > 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa > -fcall-arity -fexitification -fcase-merge -fcase-folding > -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse > -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness > -fignore-asserts -floopification -fblock-layout-cfg -fspecialise > -fcross-module-specialise -finline-generics -fstrictness > -funbox-small-strict-fields -fcpr-anal -fworker-wrapper > -fsolve-constant-dicts -fnum-constant-folding > -fno-ignore-interface-pragmas -fno-omit-interface-pragmas > > However, just by observing the output of -dshow-passes, I can see that > while -O1 applies all these optimizations, the second version does > NOT, even though I have turned on each and every one of them one by one. > > Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that > -O* should do more than just setting the flags from optLevelFlags. > What other flags are implied by -O*? > > > This email and any attachments are confidential and may also be > privileged. If you are not the intended recipient, please delete all > copies and notify the sender immediately. You may wish to refer to the > incorporation details of Standard Chartered PLC, Standard Chartered > Bank and their subsidiaries at https: //www.sc.com/en/our-locations > > Where you have a Financial Markets relationship with Standard > Chartered PLC, Standard Chartered Bank and their subsidiaries (the > "Group"), information on the regulatory standards we adhere to and how > it may affect you can be found in our Regulatory Compliance Statement > at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at > http: //www.sc.com/rcs/fm > > Insofar as this communication is not sent by the Global Research team > and contains any market commentary, the market commentary has been > prepared by the sales and/or trading desk of Standard Chartered Bank > or its affiliate. It is not and does not constitute research material, > independent research, recommendation or financial advice. Any market > commentary is for information purpose only and shall not be relied on > for any other purpose and is subject to the relevant disclaimers > available at https: > //www.sc.com/en/regulatory-disclosures/#market-disclaimer. > > Insofar as this communication is sent by the Global Research team and > contains any research materials prepared by members of the team, the > research material is for information purpose only and shall not be > relied on for any other purpose, and is subject to the relevant > disclaimers available at https: > //research.sc.com/research/api/application/static/terms-and-conditions. > > Insofar as this e-mail contains the term sheet for a proposed > transaction, by responding affirmatively to this e-mail, you agree > that you have understood the terms and conditions in the attached term > sheet and evaluated the merits and risks of the transaction. We may at > times also request you to sign the term sheet to acknowledge the same. > > Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ > for important information with respect to derivative products. > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 07:59:43 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 07:59:43 +0000 Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC Trust me when I say I understand your frustration. It is even more frustrating for me not to be able to just send a Github repo link containing my code... I'll try to make an MWE that demonstrates the problem but it will probably take quite some time. I was hoping that maybe there's some known gotcha that I'm not aware of - for example (see my other thread), I just discovered that setting optimization flags one by one isn't equal to setting them wholesale with -On, so I was *not* running specialisation in my normal (per-module) pipeline at all! Unfortunately, now that I've discovered this and made sure optLevel is set to at least 1, I am still seeing the polymorphic default implementation of >> as the only one :/ I also tried to be cheeky about the binding order and put the whole collected CoreProgram into a single Rec binder to test your guess, since that should make the actual textual order irrelevant. Unfortunately, that sill doesn't change anything :/ From: Simon Peyton Jones Sent: Monday, October 11, 2021 3:33 PM To: Erdi, Gergo ; Matthew Pickering Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC ATTENTION: This email came from an external source. Do not open attachments or click on links from unknown senders or unexpected emails. Always report suspicious emails using the Report As Phishing button in Outlook to protect the Bank and our clients. It's incredibly hard to debug this sort of thing remotely, without the ability to reproduce it. First, you are using a variant of GHC, with changes that we can only guess at. Second, even with unmodified GHC I often find that unexpected things happen - until I dig deeper and it becomes obvious! There is one odd thing about your dump: it seems to be in reverse dependency order, with functions being defined before they are used, rather than after. That would certainly stop the specialiser from working. The occurrence analyser would sort this out (literally). But that's a total guess. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 11 October 2021 03:58 To: Simon Peyton Jones >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to expose the first half of specProgram, i.e. the part that calls `go binds`. I did that because I want to apply specialisation on collected whole-program Core, not just whatever would be in scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't even have a ModGuts at hand. However, I found out from Matt's email on this thread that this is not going to be enough and eventually I'll need to figure out how I intend to apply the rewrite rules that come out of this. So for now, I am just turning on specialization in the normal pipeline by setting Opt_Specialise, Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not seeing $dm>> being specialized. Is this because I define each of "class Monad", "data IO a", "instance Monad IO", and "main", in four distinct modules? In other words, is this something I will not be able to try out until I figure out how to make a fake ModGuts and run a CoreM from outside the normal compilation pipeline, feeding it the whole-program collected CoreBinds? But if so, why is it that when I feed my whole program to just specBinds (which I can try easily since it has no ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get back an empty UsageDetails? Thanks, Gergo For reference, the relevant definitions dumped from GHC with specialization (supposedly) turned on: main = $fMonadIO_$c>> @() @() sat_sJg xmain $fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b $fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa; $dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b $dm>> = \ (@(m_ani :: Type -> Type)) ($dMonad_sIi [Occ=Once1] :: Monad m_ani) (@a_ar4) (@b_ar5) (ma_sIj [Occ=Once1] :: m_ani a_ar4) (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) -> let { sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5 [LclId] sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm From: Erdi, Gergo Sent: Thursday, October 7, 2021 9:30 AM To: Simon Peyton Jones > Cc: Montelatici, Raphael Laurent >; GHC > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones > Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Oct 11 08:05:33 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 11 Oct 2021 08:05:33 +0000 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? Maybe a documentation bug? You should update the `optLevel` field of `DynFlags` only via calling `setOptLevel`, not by setting it directly. What other design would make sense? We want to support ghc -O -fno-strictness, where the -O switches on a bunch of flags, and -fno-strictness turns off strictness. The order matters. One difficulty is that I'm not even sure where one would look for that documentation. We don't really have a comprehensive GHC User Manual description of the GHC API: Section 7.2 "Using GHC as a library" is vestigial. I would be Absolutely Fantastic, if someone (Gergo, even) felt able to flesh it out. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs Sent: 11 October 2021 08:54 To: 'GHC' Cc: Montelatici, Raphael Laurent Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC I've done some digging into this, and it turns out the DynFlag's `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn't equal setting -On for the right "n"; in fact, currently setting most of these flags does NOTHING on its own unless -On with n>=1 is *also* passed on the command line, and there is no command line flag to *only* turn on Core optimizations in the abstract, without actually turning any specific ones on. Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? From: Erdi, Gergo Sent: Monday, October 11, 2021 12:09 PM To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: -O* does more than what's in optLevelFlags? PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 08:21:12 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 08:21:12 +0000 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: PUBLIC PUBLIC But the point is, I do *not* want to set optLevel. I want to turn on individual optimizations. But as it stands today, if I turn on any optimizations, that doesn’t do anything unless I *also* set optLevel to >= 1. A nicer design in my mind would be if the semantics of optLevel is fully defined in terms of optimization flags. I want “-O1 -fno-strictness” to be exactly equivalent to “-fpolynomial-complexity -fremove-space-leaks -fstrictness -fno-strictness” which of course is equivalent to “-fpolynomial-complexity -fremove-space-leaks -fno-strictness” (assuming that the O1 flag is defined to turn on three flags that ensure polynomial complexity, remove space leaks, and turn on strictness analysis, just as a way of example). So when we compute the CoreTodos, instead of looking at the optLevel, we’d consult the set of optimizations turned on, and go “yup, at least one of these needs core-to-core simpl passes, so we better get on it”, going to the same branch that current is gated by optLevel >= 1. Would that make sense? Also, this is NOT just an API documentation issue! The GHC user’s guide itself wrongly claims: The -O* options specify convenient “packages” of optimisation flags; the -f* options described later on specify individual optimisations to be turned on/off; the -m* options specify machine-specific optimisations to be turned on/off. […] There are many options that affect the quality of code produced by GHC. Most people only have a general goal, something like “Compile quickly” or “Make my program run like greased lightning.” The following “packages” of optimisations (or lack thereof) should suffice. https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using-optimisation.html#o-convenient-packages-of-optimisation-flags I’m happy to submit a documentation patch if there is no way to actually support this model, but I would prefer much more if we can implement what is claimed in the documentation here 😊 From: Simon Peyton Jones Sent: Monday, October 11, 2021 4:06 PM To: Erdi, Gergo Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: -O* does more than what's in optLevelFlags? Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? Maybe a documentation bug? You should update the `optLevel` field of `DynFlags` only via calling `setOptLevel`, not by setting it directly. What other design would make sense? We want to support ghc -O -fno-strictness, where the -O switches on a bunch of flags, and -fno-strictness turns off strictness. The order matters. One difficulty is that I’m not even sure where one would look for that documentation. We don’t really have a comprehensive GHC User Manual description of the GHC API: Section 7.2 “Using GHC as a library” is vestigial. I would be Absolutely Fantastic, if someone (Gergo, even) felt able to flesh it out. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 11 October 2021 08:54 To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC I’ve done some digging into this, and it turns out the DynFlag’s `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn’t equal setting -On for the right “n”; in fact, currently setting most of these flags does NOTHING on its own unless -On with n>=1 is *also* passed on the command line, and there is no command line flag to *only* turn on Core optimizations in the abstract, without actually turning any specific ones on. Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? From: Erdi, Gergo Sent: Monday, October 11, 2021 12:09 PM To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: -O* does more than what's in optLevelFlags? PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Oct 11 08:33:13 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 11 Oct 2021 08:33:13 +0000 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: Oh, now I get it. I misunderstood you. But the point is, I do *not* want to set optLevel. I want to turn on individual optimizations. But as it stands today, if I turn on any optimizations, that doesn’t do anything unless I *also* set optLevel to >= 1. Yes I agree. Nothing should consult `optLevel`; indeed maybe we shouldn’t even record it permanently. The place in Pipeline that Sylvain identified is most important. So when we compute the CoreTodos, instead of looking at the optLevel, we’d consult the set of optimizations turned on, and go “yup, at least one of these needs core-to-core simpl passes, so we better get on it”, going to the same branch that current is gated by optLevel >= 1. Yes I agree with this. Another alternative might be to kill off the -O0 pipeline entirely (in GHC.Core.Opt.Pipeline.getCoreToDo) and just have one pipeline that does not-very-much when no optimisations are enabled. This would be more robust (no need to have a list of flags to consult to decide which path to follow), but could have unforeseen consequences (what happens in the -0 pipeline if all optimisations are off? Same as the -O0 pipeline?). I’d be happy with either of these changes, if someone wants to offer a patch. Certainly open a ticket with this discussion so it doesn’t get lost. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 11 October 2021 09:21 To: Simon Peyton Jones Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC PUBLIC But the point is, I do *not* want to set optLevel. I want to turn on individual optimizations. But as it stands today, if I turn on any optimizations, that doesn’t do anything unless I *also* set optLevel to >= 1. A nicer design in my mind would be if the semantics of optLevel is fully defined in terms of optimization flags. I want “-O1 -fno-strictness” to be exactly equivalent to “-fpolynomial-complexity -fremove-space-leaks -fstrictness -fno-strictness” which of course is equivalent to “-fpolynomial-complexity -fremove-space-leaks -fno-strictness” (assuming that the O1 flag is defined to turn on three flags that ensure polynomial complexity, remove space leaks, and turn on strictness analysis, just as a way of example). So when we compute the CoreTodos, instead of looking at the optLevel, we’d consult the set of optimizations turned on, and go “yup, at least one of these needs core-to-core simpl passes, so we better get on it”, going to the same branch that current is gated by optLevel >= 1. Would that make sense? Also, this is NOT just an API documentation issue! The GHC user’s guide itself wrongly claims: The -O* options specify convenient “packages” of optimisation flags; the -f* options described later on specify individual optimisations to be turned on/off; the -m* options specify machine-specific optimisations to be turned on/off. […] There are many options that affect the quality of code produced by GHC. Most people only have a general goal, something like “Compile quickly” or “Make my program run like greased lightning.” The following “packages” of optimisations (or lack thereof) should suffice. https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using-optimisation.html#o-convenient-packages-of-optimisation-flags I’m happy to submit a documentation patch if there is no way to actually support this model, but I would prefer much more if we can implement what is claimed in the documentation here 😊 From: Simon Peyton Jones > Sent: Monday, October 11, 2021 4:06 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: -O* does more than what's in optLevelFlags? Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? Maybe a documentation bug? You should update the `optLevel` field of `DynFlags` only via calling `setOptLevel`, not by setting it directly. What other design would make sense? We want to support ghc -O -fno-strictness, where the -O switches on a bunch of flags, and -fno-strictness turns off strictness. The order matters. One difficulty is that I’m not even sure where one would look for that documentation. We don’t really have a comprehensive GHC User Manual description of the GHC API: Section 7.2 “Using GHC as a library” is vestigial. I would be Absolutely Fantastic, if someone (Gergo, even) felt able to flesh it out. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 11 October 2021 08:54 To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC I’ve done some digging into this, and it turns out the DynFlag’s `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn’t equal setting -On for the right “n”; in fact, currently setting most of these flags does NOTHING on its own unless -On with n>=1 is *also* passed on the command line, and there is no command line flag to *only* turn on Core optimizations in the abstract, without actually turning any specific ones on. Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? From: Erdi, Gergo Sent: Monday, October 11, 2021 12:09 PM To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: -O* does more than what's in optLevelFlags? PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Mon Oct 11 09:46:39 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Mon, 11 Oct 2021 09:46:39 +0000 Subject: -O* does more than what's in optLevelFlags? In-Reply-To: References: Message-ID: PUBLIC PUBLIC https://gitlab.haskell.org/ghc/ghc/-/issues/20500 I tried assigning it to myself but failed; I guess I don’t have enough entitlements even to pick up tickets :/ From: Simon Peyton Jones Sent: Monday, October 11, 2021 4:33 PM To: Erdi, Gergo Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: -O* does more than what's in optLevelFlags? PUBLIC ATTENTION: This email came from an external source. Do not open attachments or click on links from unknown senders or unexpected emails. Always report suspicious emails using the Report As Phishing button in Outlook to protect the Bank and our clients. Oh, now I get it. I misunderstood you. But the point is, I do *not* want to set optLevel. I want to turn on individual optimizations. But as it stands today, if I turn on any optimizations, that doesn’t do anything unless I *also* set optLevel to >= 1. Yes I agree. Nothing should consult `optLevel`; indeed maybe we shouldn’t even record it permanently. The place in Pipeline that Sylvain identified is most important. So when we compute the CoreTodos, instead of looking at the optLevel, we’d consult the set of optimizations turned on, and go “yup, at least one of these needs core-to-core simpl passes, so we better get on it”, going to the same branch that current is gated by optLevel >= 1. Yes I agree with this. Another alternative might be to kill off the -O0 pipeline entirely (in GHC.Core.Opt.Pipeline.getCoreToDo) and just have one pipeline that does not-very-much when no optimisations are enabled. This would be more robust (no need to have a list of flags to consult to decide which path to follow), but could have unforeseen consequences (what happens in the -0 pipeline if all optimisations are off? Same as the -O0 pipeline?). I’d be happy with either of these changes, if someone wants to offer a patch. Certainly open a ticket with this discussion so it doesn’t get lost. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 11 October 2021 09:21 To: Simon Peyton Jones > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC PUBLIC But the point is, I do *not* want to set optLevel. I want to turn on individual optimizations. But as it stands today, if I turn on any optimizations, that doesn’t do anything unless I *also* set optLevel to >= 1. A nicer design in my mind would be if the semantics of optLevel is fully defined in terms of optimization flags. I want “-O1 -fno-strictness” to be exactly equivalent to “-fpolynomial-complexity -fremove-space-leaks -fstrictness -fno-strictness” which of course is equivalent to “-fpolynomial-complexity -fremove-space-leaks -fno-strictness” (assuming that the O1 flag is defined to turn on three flags that ensure polynomial complexity, remove space leaks, and turn on strictness analysis, just as a way of example). So when we compute the CoreTodos, instead of looking at the optLevel, we’d consult the set of optimizations turned on, and go “yup, at least one of these needs core-to-core simpl passes, so we better get on it”, going to the same branch that current is gated by optLevel >= 1. Would that make sense? Also, this is NOT just an API documentation issue! The GHC user’s guide itself wrongly claims: The -O* options specify convenient “packages” of optimisation flags; the -f* options described later on specify individual optimisations to be turned on/off; the -m* options specify machine-specific optimisations to be turned on/off. […] There are many options that affect the quality of code produced by GHC. Most people only have a general goal, something like “Compile quickly” or “Make my program run like greased lightning.” The following “packages” of optimisations (or lack thereof) should suffice. https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using-optimisation.html#o-convenient-packages-of-optimisation-flags I’m happy to submit a documentation patch if there is no way to actually support this model, but I would prefer much more if we can implement what is claimed in the documentation here 😊 From: Simon Peyton Jones > Sent: Monday, October 11, 2021 4:06 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: -O* does more than what's in optLevelFlags? Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? Maybe a documentation bug? You should update the `optLevel` field of `DynFlags` only via calling `setOptLevel`, not by setting it directly. What other design would make sense? We want to support ghc -O -fno-strictness, where the -O switches on a bunch of flags, and -fno-strictness turns off strictness. The order matters. One difficulty is that I’m not even sure where one would look for that documentation. We don’t really have a comprehensive GHC User Manual description of the GHC API: Section 7.2 “Using GHC as a library” is vestigial. I would be Absolutely Fantastic, if someone (Gergo, even) felt able to flesh it out. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs > On Behalf Of Erdi, Gergo via ghc-devs Sent: 11 October 2021 08:54 To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: RE: -O* does more than what's in optLevelFlags? PUBLIC I’ve done some digging into this, and it turns out the DynFlag’s `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn’t equal setting -On for the right “n”; in fact, currently setting most of these flags does NOTHING on its own unless -On with n>=1 is *also* passed on the command line, and there is no command line flag to *only* turn on Core optimizations in the abstract, without actually turning any specific ones on. Is this a documentation bug, an implementation bug (as in, if any of the relevant opts are set, then the CoreToDos should always include the optimization steps selected), or a design bug (there is no way to support this meaningfully)? From: Erdi, Gergo Sent: Monday, October 11, 2021 12:09 PM To: 'GHC' > Cc: Montelatici, Raphael Laurent > Subject: -O* does more than what's in optLevelFlags? PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReduction Opt_LlvmTBAA Opt_CallArity Opt_Exitification Opt_CaseMerge Opt_CaseFolding Opt_CmmElimCommonBlocks Opt_CmmSink Opt_CmmStaticPred Opt_CSE Opt_StgCSE Opt_EnableRewriteRules Opt_FloatIn Opt_FullLaziness Opt_IgnoreAsserts Opt_Loopification Opt_CfgBlocklayout Opt_Specialise Opt_CrossModuleSpecialise Opt_InlineGenerics Opt_Strictness Opt_UnboxSmallStrictFields Opt_CprAnal Opt_WorkerWrapper Opt_SolveConstantDicts Opt_NumConstantFolding And here are the ones that are set by O0 (the default) but not by O1: Opt_IgnoreInterfacePragmas Opt_OmitInterfacePragmas So I expected that the following two invocations of GHC would be equivalent: 1. ghc -O1 2. ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity -fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink -fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in -ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg -fspecialise -fcross-module-specialise -finline-generics -fstrictness -funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts -fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas However, just by observing the output of -dshow-passes, I can see that while -O1 applies all these optimizations, the second version does NOT, even though I have turned on each and every one of them one by one. Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* should do more than just setting the flags from optLevelFlags. What other flags are implied by -O*? This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Mon Oct 11 19:23:14 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Mon, 11 Oct 2021 15:23:14 -0400 Subject: help validating a modified compiler? Message-ID: <20211011192314.9C6AA2C1ED6@homedog.cs.tufts.edu> I've made a minor change to GHC, and before submitting a PR, I'd like to validate the change. But I don't really know how to interpret the output of the `validate` script. Mine runs for about 40 minutes and then ends in an error: # We are installing wrappers to programs by searching corresponding # wrappers. If wrapper is not found, we are attaching the common wrapper # to it. This implementation is a bit hacky and depends on consistency # of program names. For hadrian build this will work as programs have a # consistent naming procedure. if [ -L wrappers/ghc ]; then echo "ghc is a symlink"; fi ghc is a symlink cp: target 'dir/bin/ghc' is not a directory make: *** [Makefile:197: install_wrappers] Error 1 ________________________________________________________ Executed in 39.60 mins fish external usr time 146.65 mins 0.00 millis 146.65 mins sys time 9.55 mins 1.60 millis 9.55 mins I'm in the process of trying `validate` on a fresh checkout, but at 40 minutes per shot, I feel like I might be on the wrong track. Should I just create a merge request and rely on CI for the validation? Or do something else? Norman From lists at richarde.dev Mon Oct 11 20:05:32 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Mon, 11 Oct 2021 20:05:32 +0000 Subject: help validating a modified compiler? In-Reply-To: <20211011192314.9C6AA2C1ED6@homedog.cs.tufts.edu> References: <20211011192314.9C6AA2C1ED6@homedog.cs.tufts.edu> Message-ID: <010f017c70f5d7f2-012c980b-77b0-487f-acf4-1af886edd905-000000@us-east-2.amazonses.com> Speaking for myself: I have not validated locally for quite a while. I just rely on CI. You can mark an MR as a "Draft" to avoid triggering a review. Instead of validating locally, I tend to just run the testsuite on the built GHC. This can be done with hadrian/build test -j. (You might want --flavour= and --freeze1 --freeze2 there, too, to prevent recompilation.) Then I leave it to CI to do the full job. Richard > On Oct 11, 2021, at 3:23 PM, Norman Ramsey wrote: > > I've made a minor change to GHC, and before submitting a PR, I'd like to > validate the change. But I don't really know how to interpret the output > of the `validate` script. Mine runs for about 40 minutes and then ends > in an error: > > # We are installing wrappers to programs by searching corresponding > # wrappers. If wrapper is not found, we are attaching the common wrapper > # to it. This implementation is a bit hacky and depends on consistency > # of program names. For hadrian build this will work as programs have a > # consistent naming procedure. > if [ -L wrappers/ghc ]; then echo "ghc is a symlink"; fi > ghc is a symlink > cp: target 'dir/bin/ghc' is not a directory > make: *** [Makefile:197: install_wrappers] Error 1 > > ________________________________________________________ > Executed in 39.60 mins fish external > usr time 146.65 mins 0.00 millis 146.65 mins > sys time 9.55 mins 1.60 millis 9.55 mins > > I'm in the process of trying `validate` on a fresh checkout, but at 40 > minutes per shot, I feel like I might be on the wrong track. Should I > just create a merge request and rely on CI for the validation? > Or do something else? > > > Norman > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From nr at cs.tufts.edu Mon Oct 11 20:27:39 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Mon, 11 Oct 2021 16:27:39 -0400 Subject: help validating a modified compiler? In-Reply-To: <010f017c70f5d7f2-012c980b-77b0-487f-acf4-1af886edd905-000000@us-east-2.amazonses.com> (sfid-H-20211011-160620-+107.82-1@multi.osbf.lua) References: <20211011192314.9C6AA2C1ED6@homedog.cs.tufts.edu> <010f017c70f5d7f2-012c980b-77b0-487f-acf4-1af886edd905-000000@us-east-2.amazonses.com> (sfid-H-20211011-160620-+107.82-1@multi.osbf.lua) Message-ID: <20211011202739.169E12C1ACD@homedog.cs.tufts.edu> > Speaking for myself: I have not validated locally for quite a while. I just > rely on CI. I've confirmed that a fresh checkout doesn't validate. Is anyone else willing to try? If it's a problem that only I have, I'm reluctant to open an issue. > You can mark an MR as a "Draft" to avoid triggering a review. How is it so marked? Put the word "Draft" in the title? > Instead of validating locally, I tend to just run the testsuite on the > built GHC. I'll give that a try, thanks. N From klebinger.andreas at gmx.at Tue Oct 12 09:25:50 2021 From: klebinger.andreas at gmx.at (Andreas Klebinger) Date: Tue, 12 Oct 2021 11:25:50 +0200 Subject: help validating a modified compiler? In-Reply-To: <20211011202739.169E12C1ACD@homedog.cs.tufts.edu> References: <20211011192314.9C6AA2C1ED6@homedog.cs.tufts.edu> <010f017c70f5d7f2-012c980b-77b0-487f-acf4-1af886edd905-000000@us-east-2.amazonses.com> <20211011202739.169E12C1ACD@homedog.cs.tufts.edu> Message-ID: <54bbd916-bc86-4100-c762-af512800db4c@gmx.at> I tried it myself and validate fails locally as well. I've created a ticket here: https://gitlab.haskell.org/ghc/ghc/-/issues/20506 Am 11/10/2021 um 22:27 schrieb Norman Ramsey: > > Speaking for myself: I have not validated locally for quite a while. I just > > rely on CI. > > I've confirmed that a fresh checkout doesn't validate. Is anyone else > willing to try? If it's a problem that only I have, I'm reluctant to > open an issue. > > > > You can mark an MR as a "Draft" to avoid triggering a review. > > How is it so marked? Put the word "Draft" in the title? > > > Instead of validating locally, I tend to just run the testsuite on the > > built GHC. > > I'll give that a try, thanks. > > > N > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From fumiexcel at gmail.com Tue Oct 12 13:36:14 2021 From: fumiexcel at gmail.com (Fumiaki Kinoshita) Date: Tue, 12 Oct 2021 22:36:14 +0900 Subject: To allow deriving poly-kinded Generic1 instances Message-ID: I was hacking GHC to see if it's able to derive Generic1 instance for datatypes with kind (Type -> Type) -> Type by omitting some checks. I noticed that the type parameter is substituted by GHC.Types.Any, preventing higher-kinded instances from typechecking. I found a comment implying that this is intentional; in GHC.Tc.Deriv.Generic.hs:977, Alternatively, we could have avoided this problem by expanding all type synonyms on the RHSes of Rep1 instances. But we might blow up the size of these types even further by doing this, so we choose not to do so. It wasn't obvious to me if binding a parameter in the type synonym instance declaration of Rep1 cause problems, because that's what I'd do if I were to define an instance by hand. Is there any offending example? I'm also trying to make such change myself (it doesn't add a type parameter and I'm not sure why) https://gitlab.haskell.org/fumieval/ghc/-/commit/bfe7766af80d90590b6b032d1839694b82b8919a -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Tue Oct 12 16:37:50 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 12 Oct 2021 12:37:50 -0400 Subject: where to go for HLS details? Message-ID: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> Where is the place to go to talk details of the Haskell Language Server? I'm using the HLS with the GHC I have compiled from HEAD, and I am sitting on a number of difficulties: - When a project is compiled against a Stage 1 `base` library (as opposed to the one shipped with the bootstrap compiler), I am not always getting the documentation I expect. - The HLint part of the HLS seems to struggle finding modules in nested directories. - I cannot seem to get the `hiedb` command to index any files. - I'd like to set up the HLS to get to documentation via an HTTP-ish URL rather than the file:// URL that it is currently using, so that `doc-index.json` can be loaded successfully. I'm not quite ready to open a Github issue for any of these troubles just yet, but I'm not sure I can make progress on my own. Where is a good place to go for help? Norman From zubin at well-typed.com Tue Oct 12 17:07:12 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Tue, 12 Oct 2021 22:37:12 +0530 Subject: where to go for HLS details? In-Reply-To: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> References: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> Message-ID: <20211012170712.c3wo622airyrtcf6@zubin-msi> In general #haskell-language-server on libera is a good place to ask these questions. > - When a project is compiled against a Stage 1 `base` library (as > opposed to the one shipped with the bootstrap compiler), I am not > always getting the documentation I expect. > Are you getting any documentation at all, or none? If your GHC is built with hadrian, there is currently a bug (#20427) which means that the location of the haddock interfaces and html files is not correct in the package configuration. It will be fixed by !6295 (in particular https://gitlab.haskell.org/ghc/ghc/-/merge_requests/6295/diffs?commit_id=73799ad32b6009ffc50049e80b1276a306818ad3) Also how are you setting your project up to use the stage 1 base library? Do you have a specially configured .hie-bios file? > - I cannot seem to get the `hiedb` command to index any files. Ah, I see nr (I'm assuming you) asked a similar question on the IRC channel. Unfortunately I did not wake up in time to be able to answer before you left. The `hiedb` subcommand is more of a low level interface to access the guts of the database, and as such directly passes on the remaing arguments to `hiedb`, without co-operating with `haskell-language-server` very much beyond figuring out the location of the database. As such, it has no idea where the build products of files are located and can only index already generated .hie files. So to index using that command, you would have to point it at a directory containing `.hie` files. `haskell-language-server` usually puts its hie files under a project specific subdirectory of $XDG_CACHE_DIR/ghcide. For example, this works when I'm using HLS on ghc: haskell-language-server hiedb index ~/.cache/ghc-$HASH/ then to verify you can use haskell-language-server hiedb ls ~/.cache/ghc-$HASH/ > - I'd like to set up the HLS to get to documentation via an HTTP-ish > URL rather than the file:// URL that it is currently using, so > that `doc-index.json` can be loaded successfully. > I don't think this is currently possible without modifications to HLS. HLS uses the `haddock-html:` field of the package configuration to locate rendered haddock pages. Feel free to ask in case you have any other questions. I don't really know about the HLint one. Cheers, Zubin. From nr at cs.tufts.edu Tue Oct 12 18:21:24 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 12 Oct 2021 14:21:24 -0400 Subject: where to go for HLS details? In-Reply-To: <20211012170712.c3wo622airyrtcf6@zubin-msi> (sfid-H-20211012-130739-+62.87-1@multi.osbf.lua) References: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> <20211012170712.c3wo622airyrtcf6@zubin-msi> (sfid-H-20211012-130739-+62.87-1@multi.osbf.lua) Message-ID: <20211012182124.114DF2C270B@homedog.cs.tufts.edu> > In general #haskell-language-server on libera is a good place to > ask these questions. Can you recommend an IRC client? I tried using the web-based client, got limited response, and then the client destroyed all history. -------- > > - When a project is compiled against a Stage 1 `base` library (as > > opposed to the one shipped with the bootstrap compiler), I am not > > always getting the documentation I expect. > > > > Are you getting any documentation at all, or none? If your GHC is built > with hadrian, there is currently a bug (#20427) which means that the > location of the haddock interfaces and html files is not correct in > the package configuration. It will be fixed by !6295 (in particular > https://gitlab.haskell.org/ghc/ghc/-/merge_requests/6295/diffs?commit_id=73799ad32b6009ffc50049e80b1276a306818ad3) I applied the patch, removed _build/docs, and rebuilt the documentation via `./hadrian/build -j _build/docs/html/libraries/index.html`. I then restarted the HLS. Unfortunately, that change did not resolve the difficulty. As an example, the documentation for `putStrLn` reads as follows: ``` putStrLn :: String -> IO () Defined in ‘System.IO’ (base-4.15.0.0) ``` but the documentation I am hoping for (and that I get using the base library installed by `ghcup`) is ``` putStrLn :: String -> IO () Defined in ‘System.IO’ (base-4.15.0.0) The same as putStr , but adds a newline character. Documentation Source ```` The `Documentation` and `Source` strings are links; I am viewing using Emacs lsp-ui-doc. -------- > Also how are you setting your project up to use the stage 1 base library? Whoops! I meant stage 0 (so the things can be swallowed by the bootstrap compiler). It is with this `hie.yaml` file: ``` cradle: direct: arguments: ["-package-env", "-", "-clear-package-db", "-package-db", "/home/nr/asterius/ghc/_build/stage0/lib/package.conf.d", "-package-id", "ghc-9.3"] ``` Once I get everything sorted, I will add something to the GHC Wiki somewhere explaining how this works. -------- > > - I cannot seem to get the `hiedb` command to index any files. > > Ah, I see nr (I'm assuming you) asked a similar question Yes! > So to index using that command, you would have to point it at a directory > containing `.hie` files. Perfect. I had a go at this, and I made some progress. Thanks! > > - I'd like to set up the HLS to get to documentation via an HTTP-ish > > URL rather than the file:// URL that it is currently using, so > > that `doc-index.json` can be loaded successfully. > > I don't think this is currently possible without modifications to HLS. > HLS uses the `haddock-html:` field of the package configuration to locate > rendered haddock pages. Where can I find this configuration for GHC and it's accompanying packages `base` and `ghc`? I tried grepping for "haddock-html" in all the .cabal files in the GHC tree, but the only hits were in `libraries/Cabal/Cabal-tests/tests/ParserTests`, which suggests that I'm looking in the wrong place. Norman From allbery.b at gmail.com Tue Oct 12 18:27:00 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 12 Oct 2021 14:27:00 -0400 Subject: where to go for HLS details? In-Reply-To: <20211012182124.114DF2C270B@homedog.cs.tufts.edu> References: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> <20211012170712.c3wo622airyrtcf6@zubin-msi> <20211012182124.114DF2C270B@homedog.cs.tufts.edu> Message-ID: For what it's worth, I use hexchat. You may prefer to use IRC via matrix, though. On Tue, Oct 12, 2021 at 2:22 PM Norman Ramsey wrote: > > In general #haskell-language-server on libera is a good place to > > ask these questions. > > Can you recommend an IRC client? I tried using the web-based client, > got limited response, and then the client destroyed all history. > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Tue Oct 12 18:45:01 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Tue, 12 Oct 2021 14:45:01 -0400 Subject: where to go for HLS details? In-Reply-To: <20211012182124.114DF2C270B@homedog.cs.tufts.edu> References: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> <20211012170712.c3wo622airyrtcf6@zubin-msi> <20211012182124.114DF2C270B@homedog.cs.tufts.edu> Message-ID: <87wnmixeuh.fsf@smart-cactus.org> Norman Ramsey writes: > > In general #haskell-language-server on libera is a good place to > > ask these questions. > > Can you recommend an IRC client? I tried using the web-based client, > got limited response, and then the client destroyed all history. > I also use Hexchat although I have considered moving to Matrix [1]. You might consider joining via the Matrix bridge using the element.io [2] web-based client (just join `#ghc:libera.chat`). I suspect this is the lowest-friction option. Cheers, - Ben [1] https://matrix.org/ [2] https://element.io/get-started -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From zubin at well-typed.com Tue Oct 12 18:45:13 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Wed, 13 Oct 2021 00:15:13 +0530 Subject: where to go for HLS details? In-Reply-To: <20211012182124.114DF2C270B@homedog.cs.tufts.edu> References: <20211012163750.D0B8E2C270B@homedog.cs.tufts.edu> <20211012170712.c3wo622airyrtcf6@zubin-msi> <20211012182124.114DF2C270B@homedog.cs.tufts.edu> Message-ID: <20211012184513.zikpusq3h5pl6wcm@zubin-msi> >Can you recommend an IRC client? I tried using the web-based client, >got limited response, and then the client destroyed all history. I hear Matrix is a reasonable way to have a persistent connection these days. >I applied the patch, removed _build/docs, and rebuilt the >documentation via `./hadrian/build -j _build/docs/html/libraries/index.html`. >I then restarted the HLS. Unfortunately, that change did not resolve >the difficulty. As an example, the documentation for `putStrLn` reads >as follows: The bug affects GHC 9.0.1 (which I'm assuming is your boot compiler given the appearance of base-4.15.0.0). The patch hasn't been backported yet, so it would need to be applied to the ghc-9.0 tree and you would need to use that as your boot compiler if this is indeed the problem. The docs you built using the hadrian invokation are for `base-4.16.0.0` or the boot libaries for the stage2 compiler (which lives in _build/stage1). You can check that this is indeed the problem by running $ ghc-pkg -f _build/stage0/lib/package.conf.d describe base or $ ghc-pkg -f _build/stage0/lib/package.conf.d field base haddock-html You could also inspect `_build/stage0/lib/package.conf.d/base-*.conf` The 'haddock-html` field should point to a directory with all the rendered haddock HTML pages. From lists at richarde.dev Tue Oct 12 19:34:30 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Tue, 12 Oct 2021 19:34:30 +0000 Subject: GitLab summary note on review Message-ID: <010f017c75ffcc88-4f408435-13bf-4200-8922-db9328a1f9af-000000@us-east-2.amazonses.com> Hi devs, I've frequently wanted to attach a summary note to a review, unattached to any line of code. I thought this was impossible, but I see how to do it now. After making your review, with perhaps many line comments, go back to the Overview pane. Then, you can write a comment at the bottom, and, critically, add it to the review. Then, when you submit the review, the summary comment goes with it. Happy reviewing, Richard From nr at cs.tufts.edu Tue Oct 12 20:55:19 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 12 Oct 2021 16:55:19 -0400 Subject: how does a CAF become unreachable? Message-ID: <20211012205519.445912C1EDB@homedog.cs.tufts.edu> I spent the afternoon spelunking through some code and the Commentary, and I'm wondering how a CAF becomes unreachable. I gather it might have to do with GHC floating a static expression out of a context until it becomes a CAF, but I'm still not seeing how a CAF could at one point be reachable, then dynamically become unreachable. Can anyone show an example? Norman From simonpj at microsoft.com Tue Oct 12 22:10:07 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 12 Oct 2021 22:10:07 +0000 Subject: how does a CAF become unreachable? In-Reply-To: <20211012205519.445912C1EDB@homedog.cs.tufts.edu> References: <20211012205519.445912C1EDB@homedog.cs.tufts.edu> Message-ID: | Can anyone show an example? Sure xs = [1..1000] :: [Int] ys = [2..2000] :: [Float] main = do { print xs; print ys } After printing xs, the CAF for xs is unreachable and can be GC'd. No point in keeping it around. Indeed this applies from the moment (print xs) begins work. But it was main = do { print xs; print xs } then the CAF for xs remains reachable until the second (print xs) starts. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) | -----Original Message----- | From: ghc-devs On Behalf Of Norman | Ramsey | Sent: 12 October 2021 21:55 | To: ghc-devs at haskell.org | Subject: how does a CAF become unreachable? | | I spent the afternoon spelunking through some code and the Commentary, | and I'm wondering how a CAF becomes unreachable. I gather it might | have to do with GHC floating a static expression out of a context | until it becomes a CAF, but I'm still not seeing how a CAF could at | one point be reachable, then dynamically become unreachable. | | Can anyone show an example? | | | Norman | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C788a90f23049467d7636 | 08d98dc2c6ca%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637696690459 | 913210%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=8eSDcyPcNe4gSTnKJc8OQcqQI | %2B%2FDf9lSp3OksAV0H%2BU%3D&reserved=0 From ben at well-typed.com Wed Oct 13 02:47:52 2021 From: ben at well-typed.com (Ben Gamari) Date: Tue, 12 Oct 2021 22:47:52 -0400 Subject: GitLab summary note on review In-Reply-To: <010f017c75ffcc88-4f408435-13bf-4200-8922-db9328a1f9af-000000@us-east-2.amazonses.com> References: <010f017c75ffcc88-4f408435-13bf-4200-8922-db9328a1f9af-000000@us-east-2.amazonses.com> Message-ID: <87pms9y72v.fsf@smart-cactus.org> Richard Eisenberg writes: > Hi devs, > > I've frequently wanted to attach a summary note to a review, > unattached to any line of code. I thought this was impossible, but I > see how to do it now. > > After making your review, with perhaps many line comments, go back to > the Overview pane. Then, you can write a comment at the bottom, and, > critically, add it to the review. Then, when you submit the review, > the summary comment goes with it. > For what it's worth, this is a somewhat new feature that was added, at least in part, in response to our feedback. We owe some thanks to our friends at GitLab for their responsiveness. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From ryan.gl.scott at gmail.com Wed Oct 13 12:16:25 2021 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 13 Oct 2021 08:16:25 -0400 Subject: To allow deriving poly-kinded Generic1 instances Message-ID: Hello, I'm not quite sure I understand the issue you're hitting. Generic1 is poly-kinded, so I would expect it to be able to handle data types where the last type parameter has differing kinds. Can you post a complete example of the program you expect to typecheck, but doesn't? Best, Ryan -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Wed Oct 13 12:53:36 2021 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 13 Oct 2021 08:53:36 -0400 Subject: To allow deriving poly-kinded Generic1 instances In-Reply-To: References: Message-ID: Thanks for posting an example—that's very helpful to figure out what is going on. > Currently, GHC rejects the following code: > > {-# LANGUAGE DeriveGeneric #-} > {-# LANGUAGE PolyKinds #-} > import GHC.Generics > > data HKD f = Foo (f Int) (f Double) > | Bar (f Bool) > deriving Generic1 > The compilation error is > > • Can't make a derived instance of ‘Generic1 HKD’: > Constructor ‘Foo’ applies a type to an argument involving the last parameter > but the applied type is not of kind * -> *, and > Constructor ‘Foo’ applies a type to an argument involving the last parameter > but the applied type is not of kind * -> *, and > Constructor ‘Bar’ applies a type to an argument involving the last parameter > but the applied type is not of kind * -> * > • In the data declaration for ‘HKD’ I see. That error message could be worded better, in my opinion. The issue really isn't so much about the kind of `f`. If you had written `data HKD (f :: Type -> Type) = Baz (Proxy f)`, for instance, I would expect it to work. The real issue is _where_ `f` appears in the data constructors. In `Bar`, for instance, you have: > Bar (f Bool) `Generic1` is limited to data types where the last type parameter only appears as the last type argument in any field. This means that a field like `Proxy f` would be fine, as that would be represented as `Rec1 Proxy` in a `Rep1` instance. `f Bool`, on the other hand, is problematic. `GHC.Generics` doesn't have a representation type that simultaneously allows representing this field while also "focusing" on the last type parameter like `Rec1`, `Par1`, etc. would allow. The `Foo` constructor has similar issues. The error-reporting machinery for `DeriveGeneric` essentially just accumulates every issue it encounters and reports everything at once, which is why there is a duplicate error message involving `Foo`. Needless to say, this kind of error message could be improved. > Although it is possible to define a hand-rolled instance of Generic1 Really? I'm not sure how you would define a correct `Generic1` instance for `HKD` at all. What did you have in mind? Best, Ryan On Wed, Oct 13, 2021 at 8:33 AM Fumiaki Kinoshita wrote: > Currently, GHC rejects the following code: > > {-# LANGUAGE DeriveGeneric #-} > {-# LANGUAGE PolyKinds #-} > import GHC.Generics > > data HKD f = Foo (f Int) (f Double) > | Bar (f Bool) > deriving Generic1 > > The compilation error is > > • Can't make a derived instance of ‘Generic1 HKD’: > Constructor ‘Foo’ applies a type to an argument involving the last > parameter > but the applied type is not of kind * -> *, and > Constructor ‘Foo’ applies a type to an argument involving the last > parameter > but the applied type is not of kind * -> *, and > Constructor ‘Bar’ applies a type to an argument involving the last > parameter > but the applied type is not of kind * -> * > • In the data declaration for ‘HKD’ > | > 7 | deriving Generic1 > > Although it is possible to define a hand-rolled instance of Generic1, > DeriveGeneric is still restricted to Type -> Type. > > 2021年10月13日(水) 21:17 Ryan Scott : > >> Hello, >> >> I'm not quite sure I understand the issue you're hitting. Generic1 is >> poly-kinded, so I would expect it to be able to handle data types where the >> last type parameter has differing kinds. Can you post a complete example of >> the program you expect to typecheck, but doesn't? >> >> Best, >> >> Ryan >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ryan.gl.scott at gmail.com Wed Oct 13 13:48:54 2021 From: ryan.gl.scott at gmail.com (Ryan Scott) Date: Wed, 13 Oct 2021 09:48:54 -0400 Subject: To allow deriving poly-kinded Generic1 instances In-Reply-To: References: Message-ID: > I figured out that this compiles: > > data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f) > | Bar (F1 Bool f) > deriving Generic1 > > newtype F1 a f = F1 { unF1 :: f a } Yes, that's a useful trick to keep in mind. For what it's worth, I think your `F1` is the same thing as `Barbie` [1] from the `barbies` library. > Would it be a good idea to add F1 to GHC.Generics? There's a couple of issues that make me cautious about this idea: 1. This isn't an issue that's specific to `DeriveGeneric`. Other `stock` deriving strategies that deal with similar classes, such as `DeriveFunctor`, also suffer from this problem. For instance, you can't do the following: > data T a = MkT (Either a Int) deriving Functor Again, the issue is that the last type parameter (`a`) appears in a field type in a position other than as the last argument. To make _this_ work, you'd need something like `Flip` [2] from the `bifunctors` library: > data T a = MkT (Flip Either Int a) deriving Functor That leads into the second issue... 2. There are an infinite number of different type variable combinations you could conceivably add special support for. I've already mentioned `Barbie` and `Flip` above, but you could just as well put the last type parameter in other places as well: > data S1 a = MkS1 (a, Int, Int) deriving Generic1 > data S2 a = MkS2 (a, Int, Int, Int) deriving Generic1 > data S3 a = MkS3 (a, Int, Int, Int, Int) deriving Generic1 > ... And this is only if you assume that the last type parameter only appears once in each field type. You'd need even more special cases if the last type parameter appears in multiple places in a field type: > data U1 a = MkU1 (a, a) deriving Generic1 > data U2 a = MkU2 (a, a, a) deriving Generic1 > ... With all of these possibilities, it's difficult to say how far we should go with this. Generally speaking, my recommendation for people who are dissatisfied with `Generic1`'s restrictions on where the last type parameter can be placed is to not use `Generic1` at all. There are other generic programming libraries that do not have the same restrictions, such as `kind-generics` [3]. Using something like `kind-generics` avoids the need to use things like `Barbie`, `Flip`, etc. in the first place. Best, Ryan ----- [1] https://hackage.haskell.org/package/barbies-2.0.3.0/docs/Barbies.html#t:Barbie [2] https://hackage.haskell.org/package/bifunctors-5.5.11/docs/Data-Bifunctor-Flip.html#t:Flip [3] https://hackage.haskell.org/package/kind-generics On Wed, Oct 13, 2021 at 9:26 AM Fumiaki Kinoshita wrote: > Oh, I drew a conclusion too early when fiddling with a hypothetical > Generic1 instance. I now think it's not possible to define an instance with > the current kit. > > I figured out that this compiles: > > data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f) > | Bar (F1 Bool f) > deriving Generic1 > > newtype F1 a f = F1 { unF1 :: f a } > > Problem solved, thanks! > > Would it be a good idea to add F1 to GHC.Generics? Omitting metadata, it'd > derive something like > > instance Generic1 HKD where > type Rep1 HKD = F1 Int :*: F1 Double :+: F1 Bool > from1 (Foo a b) = L1 (F1 a :*: F1 b) > from1 (Bar c) = R1 (F1 c) > to1 (L1 (F1 a :*: F1 b)) = Foo a b > to1 (R1 (F1 c)) = Bar c > > I suppose it doesn't affect existing Generic1 instances and uses, so I > don't expect breakages by adding this > > ... > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Thu Oct 14 03:43:35 2021 From: ekmett at gmail.com (Edward Kmett) Date: Wed, 13 Oct 2021 23:43:35 -0400 Subject: To allow deriving poly-kinded Generic1 instances In-Reply-To: References: Message-ID: I use the same F1 trick (with the same name and for the same reason) in the HEAD branch of hkd and distributive, but I admit it is a bit frustrating, because then I have to expose pattern synonyms to hide its boilerplate from users. e.g. https://github.com/ekmett/hkd/blob/85cee5aa594b66f2d03d6366df776ced742e4635/src/Data/HKD.hs#L168 ... https://github.com/ekmett/hkd/blob/85cee5aa594b66f2d03d6366df776ced742e4635/src/Data/HKD.hs#L252 Adding an F1 or the like to GHC.Generics that was used automatically to handle application of the last "1" argument to some other type in turn would go a long way towards plugging that hole in the vocabulary of stock GHC.Generics. Other generics libraries exist, but they don't get quite the same attention and user support. -Edward On Wed, Oct 13, 2021 at 9:49 AM Ryan Scott wrote: > > I figured out that this compiles: > > > > data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f) > > | Bar (F1 Bool f) > > deriving Generic1 > > > > newtype F1 a f = F1 { unF1 :: f a } > > Yes, that's a useful trick to keep in mind. For what it's worth, I think > your `F1` is the same thing as `Barbie` [1] from the `barbies` library. > > > Would it be a good idea to add F1 to GHC.Generics? > > There's a couple of issues that make me cautious about this idea: > > 1. This isn't an issue that's specific to `DeriveGeneric`. Other `stock` > deriving strategies that deal with similar classes, such as > `DeriveFunctor`, also suffer from this problem. For instance, you can't do > the following: > > > data T a = MkT (Either a Int) deriving Functor > > Again, the issue is that the last type parameter (`a`) appears in a > field type in a position other than as the last argument. To make _this_ > work, you'd need something like `Flip` [2] from the `bifunctors` library: > > > data T a = MkT (Flip Either Int a) deriving Functor > > That leads into the second issue... > 2. There are an infinite number of different type variable combinations > you could conceivably add special support for. I've already mentioned > `Barbie` and `Flip` above, but you could just as well put the last type > parameter in other places as well: > > > data S1 a = MkS1 (a, Int, Int) deriving Generic1 > > data S2 a = MkS2 (a, Int, Int, Int) deriving Generic1 > > data S3 a = MkS3 (a, Int, Int, Int, Int) deriving Generic1 > > ... > > And this is only if you assume that the last type parameter only > appears once in each field type. You'd need even more special cases if the > last type parameter appears in multiple places in a field type: > > > data U1 a = MkU1 (a, a) deriving Generic1 > > data U2 a = MkU2 (a, a, a) deriving Generic1 > > ... > > With all of these possibilities, it's difficult to say how far we > should go with this. > > Generally speaking, my recommendation for people who are dissatisfied with > `Generic1`'s restrictions on where the last type parameter can be placed is > to not use `Generic1` at all. There are other generic programming libraries > that do not have the same restrictions, such as `kind-generics` [3]. Using > something like `kind-generics` avoids the need to use things like `Barbie`, > `Flip`, etc. in the first place. > > Best, > > Ryan > ----- > [1] > https://hackage.haskell.org/package/barbies-2.0.3.0/docs/Barbies.html#t:Barbie > [2] > https://hackage.haskell.org/package/bifunctors-5.5.11/docs/Data-Bifunctor-Flip.html#t:Flip > [3] https://hackage.haskell.org/package/kind-generics > > On Wed, Oct 13, 2021 at 9:26 AM Fumiaki Kinoshita > wrote: > >> Oh, I drew a conclusion too early when fiddling with a hypothetical >> Generic1 instance. I now think it's not possible to define an instance with >> the current kit. >> >> I figured out that this compiles: >> >> data HKD (f :: Type -> Type) = Foo (F1 Int f) (F1 Double f) >> | Bar (F1 Bool f) >> deriving Generic1 >> >> newtype F1 a f = F1 { unF1 :: f a } >> >> Problem solved, thanks! >> >> Would it be a good idea to add F1 to GHC.Generics? Omitting metadata, >> it'd derive something like >> >> instance Generic1 HKD where >> type Rep1 HKD = F1 Int :*: F1 Double :+: F1 Bool >> from1 (Foo a b) = L1 (F1 a :*: F1 b) >> from1 (Bar c) = R1 (F1 c) >> to1 (L1 (F1 a :*: F1 b)) = Foo a b >> to1 (R1 (F1 c)) = Bar c >> >> I suppose it doesn't affect existing Generic1 instances and uses, so I >> don't expect breakages by adding this >> >> ... >> > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.redelings at gmail.com Thu Oct 14 15:59:32 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Thu, 14 Oct 2021 11:59:32 -0400 Subject: Resources on how to implement (Haskell 98) kind checking? Message-ID: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> Hi, I asked about this on Haskell-Cafe, and was recommended to ask here instead.  Any help is much appreciated! 1. I'm looking for resources that describe how to implement kind Haskell 98 checking.  Does anyone have any good suggestions?  So far, the papers that I've looked at all fall short in different ways: * Mark Jones's paper "A system of constructor classes":  This paper contains a kind-aware type-inference algorithm, but no kind inference algorithm.  The closest it comes is the rule:     C :: k' -> k   and   C' :: k'   =>   C C' :: k * The THIH paper doesn't have an algorithm for kind checking.  It assumes that every type variable already has a kind. * The 2010 Report helpfully mentions substituting any remaining kind variables with *.  But it refers to "A system of constructor classes" for an algorithm. * The PolyKinds paper was the most helpful thing I've found, but it doesn't cover type classes.  I'm also not sure that all implementers can follow algorithm descriptions that are laid out as inference rules, but maybe that could be fixed with a few hints about how to run the rules in reverse.  Also, in practice I think an implementer would want to follow GHC in specifying the initial kind of a data type as k1 -> k2 -> ... kn -> *. * I've looked at the source code to GHC, and some of the longer notes were quite helpful.  However, it is hard to follow for a variety of reasons.  It isn't laid out like an algorithm description, and the complexity to handle options like PolyKinds and DataKinds makes the code harder to follow. 2. The following question (which I have maybe kind of answered now, but could use more advice on) is an example of what I am hoping such documentation would explain: > Q: How do you handle type variables that are present in class methods, > but are not type class parameters? If there are multiple types/classes > in a single recursive group, the kind of such type variables might not > be fully resolved until a later type-or-class is processed.  Is there > a recommended approach? > > I can see two ways to proceed: > > i) First determine the kinds of all the data types, classes, and type > synonyms.  Then perform a second pass over each type or class to > determine the kinds of type variables (in class methods) that are not > type class parameters. > > ii) Alternatively, record the kind of each type variable as it is > encountered -- even though such kinds may contain unification kind > variables.  After visiting all types-or-classes in the recursive > group, replace any kind variables with their definition, or with a * > if there is no definition. > > I've currently implement approach i), which requires doing kind > inference on class methods twice. > Further investigation revealed that GHC takes yet another approach (I think): iii) Represent kinds with modifiable variables.  Substitution can be implemented by modifying kind variables in-place.  This is (I think) called "zonking" in the GHC sources. This solves a small mystery for me, since I previously thought that zonking was just replacing remaining kind variables with '*'.  And indeed this seems to be an example of zonking, but not what zonking is (I think). Zonking looks painful to implement, but approach (i) might require multiple passes over types to update the kind of type variables, which might be worse... 3. I'm curious now how many other pieces of software besides GHC have implemented kind inference... -BenRI -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Fri Oct 15 04:35:26 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Fri, 15 Oct 2021 04:35:26 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) Message-ID: PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn't *do* anything. From: Erdi, Gergo Sent: Monday, October 11, 2021 4:00 PM To: Simon Peyton Jones ; Matthew Pickering Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Trust me when I say I understand your frustration. It is even more frustrating for me not to be able to just send a Github repo link containing my code... I'll try to make an MWE that demonstrates the problem but it will probably take quite some time. I was hoping that maybe there's some known gotcha that I'm not aware of - for example (see my other thread), I just discovered that setting optimization flags one by one isn't equal to setting them wholesale with -On, so I was *not* running specialisation in my normal (per-module) pipeline at all! Unfortunately, now that I've discovered this and made sure optLevel is set to at least 1, I am still seeing the polymorphic default implementation of >> as the only one :/ I also tried to be cheeky about the binding order and put the whole collected CoreProgram into a single Rec binder to test your guess, since that should make the actual textual order irrelevant. Unfortunately, that sill doesn't change anything :/ From: Simon Peyton Jones > Sent: Monday, October 11, 2021 3:33 PM To: Erdi, Gergo >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC ATTENTION: This email came from an external source. Do not open attachments or click on links from unknown senders or unexpected emails. Always report suspicious emails using the Report As Phishing button in Outlook to protect the Bank and our clients. It's incredibly hard to debug this sort of thing remotely, without the ability to reproduce it. First, you are using a variant of GHC, with changes that we can only guess at. Second, even with unmodified GHC I often find that unexpected things happen - until I dig deeper and it becomes obvious! There is one odd thing about your dump: it seems to be in reverse dependency order, with functions being defined before they are used, rather than after. That would certainly stop the specialiser from working. The occurrence analyser would sort this out (literally). But that's a total guess. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 11 October 2021 03:58 To: Simon Peyton Jones >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to expose the first half of specProgram, i.e. the part that calls `go binds`. I did that because I want to apply specialisation on collected whole-program Core, not just whatever would be in scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't even have a ModGuts at hand. However, I found out from Matt's email on this thread that this is not going to be enough and eventually I'll need to figure out how I intend to apply the rewrite rules that come out of this. So for now, I am just turning on specialization in the normal pipeline by setting Opt_Specialise, Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not seeing $dm>> being specialized. Is this because I define each of "class Monad", "data IO a", "instance Monad IO", and "main", in four distinct modules? In other words, is this something I will not be able to try out until I figure out how to make a fake ModGuts and run a CoreM from outside the normal compilation pipeline, feeding it the whole-program collected CoreBinds? But if so, why is it that when I feed my whole program to just specBinds (which I can try easily since it has no ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get back an empty UsageDetails? Thanks, Gergo For reference, the relevant definitions dumped from GHC with specialization (supposedly) turned on: main = $fMonadIO_$c>> @() @() sat_sJg xmain $fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b $fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa; $dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b $dm>> = \ (@(m_ani :: Type -> Type)) ($dMonad_sIi [Occ=Once1] :: Monad m_ani) (@a_ar4) (@b_ar5) (ma_sIj [Occ=Once1] :: m_ani a_ar4) (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) -> let { sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5 [LclId] sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm From: Erdi, Gergo Sent: Thursday, October 7, 2021 9:30 AM To: Simon Peyton Jones > Cc: Montelatici, Raphael Laurent >; GHC > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones > Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Main.hs Type: application/octet-stream Size: 8989 bytes Desc: Main.hs URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Use.src Type: application/octet-stream Size: 128 bytes Desc: Use.src URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Class.src Type: application/octet-stream Size: 143 bytes Desc: Class.src URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Instance.src Type: application/octet-stream Size: 177 bytes Desc: Instance.src URL: From gergo at erdi.hu Fri Oct 15 10:41:04 2021 From: gergo at erdi.hu (=?UTF-8?B?R2VyZ8WRIMOJcmRp?=) Date: Fri, 15 Oct 2021 18:41:04 +0800 Subject: Resources on how to implement (Haskell 98) kind checking? In-Reply-To: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> References: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> Message-ID: Using mutable references for type metavariables is an implementation optimization: unifying a metavariable with a kind can then be cheaply implemented by replacing the metavar's content with the kind. After you are done with unification, you don't need metavariables anymore. If this were HM, you'd generalize remaining metavariables into type variables. But for kinds, remaining metavariables are defaulted to * in Haskell 98. (Of course, if you used PolyKinds, kind metavars would also be generalized). Zonking is the process of traversing a type / kind with these mutable references and replacing each mutable reference with its value, thereby "baking in" its current solution. If you encounter a mutable reference that doesn't contain anything, it means the metavar it represents hasn't been constrained in any way -- so you can just choose * for them. People seem to have upvoted my SO answer about GHC's zonking so you might find it useful as well: https://stackoverflow.com/a/31890743/477476 On Fri, Oct 15, 2021 at 12:01 AM Benjamin Redelings wrote: > > Hi, > > I asked about this on Haskell-Cafe, and was recommended to ask here instead. Any help is much appreciated! > > 1. I'm looking for resources that describe how to implement kind Haskell 98 checking. Does anyone have any good suggestions? So far, the papers that I've looked at all fall short in different ways: > > * Mark Jones's paper "A system of constructor classes": This paper contains a kind-aware type-inference algorithm, but no kind inference algorithm. The closest it comes is the rule: > > C :: k' -> k and C' :: k' => C C' :: k > > * The THIH paper doesn't have an algorithm for kind checking. It assumes that every type variable already has a kind. > > * The 2010 Report helpfully mentions substituting any remaining kind variables with *. But it refers to "A system of constructor classes" for an algorithm. > > * The PolyKinds paper was the most helpful thing I've found, but it doesn't cover type classes. I'm also not sure that all implementers can follow algorithm descriptions that are laid out as inference rules, but maybe that could be fixed with a few hints about how to run the rules in reverse. Also, in practice I think an implementer would want to follow GHC in specifying the initial kind of a data type as k1 -> k2 -> ... kn -> *. > > * I've looked at the source code to GHC, and some of the longer notes were quite helpful. However, it is hard to follow for a variety of reasons. It isn't laid out like an algorithm description, and the complexity to handle options like PolyKinds and DataKinds makes the code harder to follow. > > > > 2. The following question (which I have maybe kind of answered now, but could use more advice on) is an example of what I am hoping such documentation would explain: > > Q: How do you handle type variables that are present in class methods, but are not type class parameters? If there are multiple types/classes in a single recursive group, the kind of such type variables might not be fully resolved until a later type-or-class is processed. Is there a recommended approach? > > I can see two ways to proceed: > > i) First determine the kinds of all the data types, classes, and type synonyms. Then perform a second pass over each type or class to determine the kinds of type variables (in class methods) that are not type class parameters. > > ii) Alternatively, record the kind of each type variable as it is encountered -- even though such kinds may contain unification kind variables. After visiting all types-or-classes in the recursive group, replace any kind variables with their definition, or with a * if there is no definition. > > I've currently implement approach i), which requires doing kind inference on class methods twice. > > Further investigation revealed that GHC takes yet another approach (I think): > > iii) Represent kinds with modifiable variables. Substitution can be implemented by modifying kind variables in-place. This is (I think) called "zonking" in the GHC sources. > > This solves a small mystery for me, since I previously thought that zonking was just replacing remaining kind variables with '*'. And indeed this seems to be an example of zonking, but not what zonking is (I think). > > Zonking looks painful to implement, but approach (i) might require multiple passes over types to update the kind of type variables, which might be worse... > > > > 3. I'm curious now how many other pieces of software besides GHC have implemented kind inference... > > > -BenRI > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From simonpj at microsoft.com Fri Oct 15 16:52:26 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 15 Oct 2021 16:52:26 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module 'Paths_ghc_lib' Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 15 October 2021 05:35 To: Simon Peyton Jones ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn't *do* anything. From: Erdi, Gergo Sent: Monday, October 11, 2021 4:00 PM To: Simon Peyton Jones >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Trust me when I say I understand your frustration. It is even more frustrating for me not to be able to just send a Github repo link containing my code... I'll try to make an MWE that demonstrates the problem but it will probably take quite some time. I was hoping that maybe there's some known gotcha that I'm not aware of - for example (see my other thread), I just discovered that setting optimization flags one by one isn't equal to setting them wholesale with -On, so I was *not* running specialisation in my normal (per-module) pipeline at all! Unfortunately, now that I've discovered this and made sure optLevel is set to at least 1, I am still seeing the polymorphic default implementation of >> as the only one :/ I also tried to be cheeky about the binding order and put the whole collected CoreProgram into a single Rec binder to test your guess, since that should make the actual textual order irrelevant. Unfortunately, that sill doesn't change anything :/ From: Simon Peyton Jones > Sent: Monday, October 11, 2021 3:33 PM To: Erdi, Gergo >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC ATTENTION: This email came from an external source. Do not open attachments or click on links from unknown senders or unexpected emails. Always report suspicious emails using the Report As Phishing button in Outlook to protect the Bank and our clients. It's incredibly hard to debug this sort of thing remotely, without the ability to reproduce it. First, you are using a variant of GHC, with changes that we can only guess at. Second, even with unmodified GHC I often find that unexpected things happen - until I dig deeper and it becomes obvious! There is one odd thing about your dump: it seems to be in reverse dependency order, with functions being defined before they are used, rather than after. That would certainly stop the specialiser from working. The occurrence analyser would sort this out (literally). But that's a total guess. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 11 October 2021 03:58 To: Simon Peyton Jones >; Matthew Pickering > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to expose the first half of specProgram, i.e. the part that calls `go binds`. I did that because I want to apply specialisation on collected whole-program Core, not just whatever would be in scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't even have a ModGuts at hand. However, I found out from Matt's email on this thread that this is not going to be enough and eventually I'll need to figure out how I intend to apply the rewrite rules that come out of this. So for now, I am just turning on specialization in the normal pipeline by setting Opt_Specialise, Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not seeing $dm>> being specialized. Is this because I define each of "class Monad", "data IO a", "instance Monad IO", and "main", in four distinct modules? In other words, is this something I will not be able to try out until I figure out how to make a fake ModGuts and run a CoreM from outside the normal compilation pipeline, feeding it the whole-program collected CoreBinds? But if so, why is it that when I feed my whole program to just specBinds (which I can try easily since it has no ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get back an empty UsageDetails? Thanks, Gergo For reference, the relevant definitions dumped from GHC with specialization (supposedly) turned on: main = $fMonadIO_$c>> @() @() sat_sJg xmain $fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b $fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa; $dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b $dm>> = \ (@(m_ani :: Type -> Type)) ($dMonad_sIi [Occ=Once1] :: Monad m_ani) (@a_ar4) (@b_ar5) (ma_sIj [Occ=Once1] :: m_ani a_ar4) (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) -> let { sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5 [LclId] sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm From: Erdi, Gergo Sent: Thursday, October 7, 2021 9:30 AM To: Simon Peyton Jones > Cc: Montelatici, Raphael Laurent >; GHC > Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones > Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo > Cc: Montelatici, Raphael Laurent >; GHC > Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*) Grego, Yes I think that should auto-specialise. Which version of GHC are you using? Do you have this patch? commit ef0135934fe32da5b5bb730dbce74262e23e72e8 Author: Simon Peyton Jones simonpj at microsoft.com Date: Thu Apr 8 22:42:31 2021 +0100 Make the specialiser handle polymorphic specialisation Here's why I ask. The call $fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b indeed applies $dm>> to $fMonadIO, but it also applies it to a and b. In the version of GHC you have, maybe that stops the call from floating up to the definition site, and being used to specialise it. Can you make a repro case without your plugin? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Fri Oct 15 17:37:31 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Fri, 15 Oct 2021 17:37:31 +0000 Subject: Resources on how to implement (Haskell 98) kind checking? In-Reply-To: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> References: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> Message-ID: <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> > On Oct 14, 2021, at 11:59 AM, Benjamin Redelings wrote: > > I asked about this on Haskell-Cafe, and was recommended to ask here instead. Any help is much appreciated! > I saw your post over there, but haven't had time to respond.... but this retelling of the story makes it easier to respond, so I'll do so here. > * The PolyKinds paper was the most helpful thing I've found, but it doesn't cover type classes. I'm also not sure that all implementers can follow algorithm descriptions that are laid out as inference rules, but maybe that could be fixed with a few hints about how to run the rules in reverse. Also, in practice I think an implementer would want to follow GHC in specifying the initial kind of a data type as k1 -> k2 -> ... kn -> *. > What is unique about type classes? It seems like you're worried about locally quantified type variables in method types, but (as far as kind inference is concerned) those are very much like existential variables in data constructors. So perhaps take the bit about existential variables from the PolyKinds part of that paper and combine it with the Haskell98 part. It's true that many implementors may find the notation in that paper to be a barrier, but you just have to read the rules clockwise, starting from the bottom left and ending on the bottom right. :) > > 2. The following question (which I have maybe kind of answered now, but could use more advice on) is an example of what I am hoping such documentation would explain: > > >> Q: How do you handle type variables that are present in class methods, but are not type class parameters? If there are multiple types/classes in a single recursive group, the kind of such type variables might not be fully resolved until a later type-or-class is processed. Is there a recommended approach? >> >> I can see two ways to proceed: >> >> i) First determine the kinds of all the data types, classes, and type synonyms. Then perform a second pass over each type or class to determine the kinds of type variables (in class methods) that are not type class parameters. This won't work. class C a where meth :: a b -> b Int You have to know the kind of local b to learn the kind of class-variable a. So you have to do it all at once. >> >> ii) Alternatively, record the kind of each type variable as it is encountered -- even though such kinds may contain unification kind variables. After visiting all types-or-classes in the recursive group, replace any kind variables with their definition, or with a * if there is no definition. >> >> I've currently implement approach i), which requires doing kind inference on class methods twice. >> > Further investigation revealed that GHC takes yet another approach (I think): > > iii) Represent kinds with modifiable variables. Substitution can be implemented by modifying kind variables in-place. This is (I think) called "zonking" in the GHC sources. I don't really see the difference between (ii) and (iii). Maybe (ii) records the kinds in a table somewhere, while (iii) records them "in" the kind variables themselves, but that's not so different, I think. > > This solves a small mystery for me, since I previously thought that zonking was just replacing remaining kind variables with '*'. And indeed this seems to be an example of zonking, but not what zonking is (I think). We can imagine that, instead of mutation, we build a substitution mapping unification variables to types (or kinds). This would be stored just as a simple mapping or dictionary structure. No mutation. As we learn about a unification variable, we just add to the mapping. If we did this, zonking would be the act of applying the substitution, replacing known unification variables with their values. It just so happens that GHC builds a mapping by using mutable cells in memory, but that's just an implementation detail: zonking is still just applying the substitution. Zonking does not replace anything with *. Well, functions that have "zonk" in their name may do this. But it is not really logically part of the zonking operation. If you like, you can pretend that, after zonking a program, we take a separate pass replacing any yet-unfilled kind-level unification variables with *. Sometimes, this is called "zapping" in GHC, I believe. > > Zonking looks painful to implement, but approach (i) might require multiple passes over types to update the kind of type variables, which might be worse... Zonking is a bit laborious to implement, but not painful. Laborious, because it requires a full pass over the AST. Not painful, because all it's trying to do is replace type/kind variables with substitutions: each individual piece of the puzzle is quite simple. I hope this is helpful! Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Oct 18 07:29:07 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 18 Oct 2021 07:29:07 +0000 Subject: gitlab.haskell.org Message-ID: I'm getting "502" from gitlab.haskell.org. Is it just me? Thanks Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) -------------- next part -------------- An HTML attachment was scrubbed... URL: From zubin at well-typed.com Mon Oct 18 08:09:21 2021 From: zubin at well-typed.com (Zubin Duggal) Date: Mon, 18 Oct 2021 13:39:21 +0530 Subject: gitlab.haskell.org In-Reply-To: References: Message-ID: <20211018080921.kfs2le4q2fol3y2f@zubin-msi> It is not just you, Gitlab has been unstable since yesterday due to a lack of disk space. On 21/10/18 07:29, Simon Peyton Jones via ghc-devs wrote: >I'm getting "502" from gitlab.haskell.org. Is it just me? > >Thanks > >Simon > >PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > >_______________________________________________ >ghc-devs mailing list >ghc-devs at haskell.org >http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From matthewtpickering at gmail.com Mon Oct 18 09:12:07 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Mon, 18 Oct 2021 10:12:07 +0100 Subject: gitlab.haskell.org In-Reply-To: <20211018080921.kfs2le4q2fol3y2f@zubin-msi> References: <20211018080921.kfs2le4q2fol3y2f@zubin-msi> Message-ID: I restarted the service and things appear to be working atm.. but I don't understand how the volumes are configured on the machine so will have to wait for Ben to fix it properly. On Mon, Oct 18, 2021 at 9:11 AM Zubin Duggal wrote: > > It is not just you, Gitlab has been unstable since yesterday due to a > lack of disk space. > > On 21/10/18 07:29, Simon Peyton Jones via ghc-devs wrote: > >I'm getting "502" from gitlab.haskell.org. Is it just me? > > > >Thanks > > > >Simon > > > >PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > >_______________________________________________ > >ghc-devs mailing list > >ghc-devs at haskell.org > >http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Mon Oct 18 09:22:44 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 18 Oct 2021 10:22:44 +0100 Subject: gitlab.haskell.org In-Reply-To: References: <20211018080921.kfs2le4q2fol3y2f@zubin-msi> Message-ID: <20211018092244.GB23953@cloudinit-builder> If a sponsor (perhaps the HF) could pay for GitLab to host the service on our behalf would that be helpful? I don't know whether GHC development relies deeply on some aspect of our self-hosted setup. (I suspect it does because otherwise we'd likely be using a free GitLab tier for open source organisations, but I thought the question was worth asking.) Tom On Mon, Oct 18, 2021 at 10:12:07AM +0100, Matthew Pickering wrote: > I restarted the service and things appear to be working atm.. but I > don't understand how the volumes are configured on the machine so will > have to wait for Ben to fix it properly. > > On Mon, Oct 18, 2021 at 9:11 AM Zubin Duggal wrote: > > It is not just you, Gitlab has been unstable since yesterday due to a > > lack of disk space. > > > > On 21/10/18 07:29, Simon Peyton Jones via ghc-devs wrote: > > >I'm getting "502" from gitlab.haskell.org. Is it just me? From ben at well-typed.com Mon Oct 18 13:48:37 2021 From: ben at well-typed.com (Ben Gamari) Date: Mon, 18 Oct 2021 09:48:37 -0400 Subject: GitLab outage Message-ID: <87a6j6xx3y.fsf@smart-cactus.org> Hello all, Unfortunately yesterday gitlab.haskell.org yet again ran out of disk space. It is currently being migrated to another machine and in the meantime things may be a bit flaky. Many apologies for the inconvenience. More updates will be coming as the situation develops. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From nr at cs.tufts.edu Mon Oct 18 17:21:32 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Mon, 18 Oct 2021 13:21:32 -0400 Subject: GitLab outage In-Reply-To: <87a6j6xx3y.fsf@smart-cactus.org> (sfid-H-20211018-094933-+65.62-1@multi.osbf.lua) References: <87a6j6xx3y.fsf@smart-cactus.org> (sfid-H-20211018-094933-+65.62-1@multi.osbf.lua) Message-ID: <20211018172132.DF4B32C2FFB@homedog.cs.tufts.edu> > Unfortunately yesterday gitlab.haskell.org yet again ran out of disk > space. It is currently being migrated to another machine and in the > meantime things may be a bit flaky. Many apologies for the > inconvenience. More updates will be coming as the situation develops. I see that gitlab is back up, but also that its host key has changed. That would make sense if you have migrated to an existing machine with its own configuration. But could you kindly please confirm that fingerprint for the new host is expected to be as follows? The fingerprint for the ED25519 key sent by the remote host is SHA256:pPSesloVW0X6zUe/fJ+ZSK8NttS0WiDlFt/VDS06Ugs. Norman From ben at well-typed.com Mon Oct 18 17:31:01 2021 From: ben at well-typed.com (Ben Gamari) Date: Mon, 18 Oct 2021 13:31:01 -0400 Subject: GitLab outage In-Reply-To: <87a6j6xx3y.fsf@smart-cactus.org> References: <87a6j6xx3y.fsf@smart-cactus.org> Message-ID: <877deaxmu2.fsf@smart-cactus.org> Ben Gamari writes: > Hello all, > > Unfortunately yesterday gitlab.haskell.org yet again ran out of disk > space. It is currently being migrated to another machine and in the > meantime things may be a bit flaky. Many apologies for the > inconvenience. More updates will be coming as the situation develops. > Hello all, I have finished bringing up GitLab on a new instance which I'm hoping should have enough storage for many years to come. Apologies for the down-time and thanks for your patience. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From nr at cs.tufts.edu Mon Oct 18 17:46:12 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Mon, 18 Oct 2021 13:46:12 -0400 Subject: GHC.StgToCmm.Monad documentation out of sync? Message-ID: <20211018174612.2D3542C3005@homedog.cs.tufts.edu> All, I'm looking at the paragraph starting on line 271 of GHC.StgToCmm.Monad, which purports to explain ReturnKind. But the labels mentioned in the paragraph don't seem to match the preceding code example. Also, I don't understand why only one branch of the `case` expression seems to be protected by a heap-limit check. I understand what I'm seeing well enough to fear that something is wrong, but not well enough to fix it. Is someone else willing to have a look and maybe we can repair the documentation together? Noramn From ben at well-typed.com Mon Oct 18 23:39:37 2021 From: ben at well-typed.com (Ben Gamari) Date: Mon, 18 Oct 2021 19:39:37 -0400 Subject: GitLab outage In-Reply-To: <20211018172132.DF4B32C2FFB@homedog.cs.tufts.edu> References: <87a6j6xx3y.fsf@smart-cactus.org> <20211018172132.DF4B32C2FFB@homedog.cs.tufts.edu> Message-ID: <874k9dykbd.fsf@smart-cactus.org> Norman Ramsey writes: > > Unfortunately yesterday gitlab.haskell.org yet again ran out of disk > > space. It is currently being migrated to another machine and in the > > meantime things may be a bit flaky. Many apologies for the > > inconvenience. More updates will be coming as the situation develops. > > I see that gitlab is back up, but also that its host key has changed. > That would make sense if you have migrated to an existing machine with > its own configuration. But could you kindly please confirm that > fingerprint for the new host is expected to be as follows? > Indeed I realized the mistake shortly after sending my previous email and restored the host key. The host keys are: gitlab.haskell.org ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAIA7ltOZyaULDgxE3Vw6RgQVp+OPKQi79ssUenbhdWy36 gitlab.haskell.org ssh-rsa AAAAB3NzaC1yc2EAAAADAQABAAACAQDSzzl8mwY6ohtW6MftKaQfta8yTL8cTxtA7lcueo2mkPpwBBQ7FA6z3nFATx25QwdV7fa7DuNRDX57f/a/W7+wMhXZ6yyQr+gwr0h4vdZ8Nt4XNfNdkdGw4fZKRApWxyvfSkxjs/E9+G0o3eQLspxjVohBkmkcsowpFUI5Aazv/K6QIf1gKt+4iPvYcB/dBJ1yF1qmpayz4htrKyUC5l3GCBEwvMdAjIQ2bX8pyjTtqcJDLosAVzQ5wprkdgkL29MgJXEbM+B1d1log0hnX4AsbOlL7tWhTO1Je2hSuEeiVaDDPFUyCoGQRFDrisQU5lb8NrzuN3jpNc+PxOHbXHfaTppAoED/++UepvgtLF1zUM13cRk56YmpmABOa48W72VJuzLLm8DF+KBWBs6TDuVk3y9z/SS6zDS0VGkHotldopW2kpsjErJIdWVKIL3RP/Flay7mzl3l/izIMTHXXKMxV3/+XaBjG/gDOCld3JjORQXah2hvJfvXeNaePE1RKAMS63cj3XTE77fsYH7VmEdE34RTBDtsZR5WhEjdf29hjEcQDPf0vDphxRHr6IqUSwVcd7ps6nVoccTfaepJm62IIXDgOsc2piWl2xXNZJVtph6U+MzsPDSSbu1MTwalwgqpApcYK7ZzUjGHA7+NBhjjSuUZO6eHzwxjAn0FXZyrpQ== Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From ben at smart-cactus.org Mon Oct 18 23:59:41 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Mon, 18 Oct 2021 19:59:41 -0400 Subject: GHC.StgToCmm.Monad documentation out of sync? In-Reply-To: <20211018174612.2D3542C3005@homedog.cs.tufts.edu> References: <20211018174612.2D3542C3005@homedog.cs.tufts.edu> Message-ID: <871r4hyjdy.fsf@smart-cactus.org> Norman Ramsey writes: > All, > > I'm looking at the paragraph starting on line 271 of GHC.StgToCmm.Monad, > which purports to explain ReturnKind. But the labels mentioned in the > paragraph don't seem to match the preceding code example. Also, I don't > understand why only one branch of the `case` expression seems to > be protected by a heap-limit check. > > I understand what I'm seeing well enough to fear that something is > wrong, but not well enough to fix it. Is someone else willing to > have a look and maybe we can repair the documentation together? > Below is my understanding: * My suspicion here is that the paragraph starting on 271 would be clearer if it started with the word "However, ". That is, the preceding code snippet is what one would naively expect and the paragraph then explains what we would rather want the compiler to emit. * I also suspect that the reference to L4 should really read as L5. * The fact that there is only one heap check is likely merely for conciseness. The heap check shown is the check for the True branch. The code represented by "" would include its own heap check, but the author felt it was not important to list this explicitly since it was secondary to the message of the Note. Does this seem reasonable to you? Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From ben at smart-cactus.org Tue Oct 19 01:23:01 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Mon, 18 Oct 2021 21:23:01 -0400 Subject: gitlab.haskell.org In-Reply-To: <20211018092244.GB23953@cloudinit-builder> References: <20211018080921.kfs2le4q2fol3y2f@zubin-msi> <20211018092244.GB23953@cloudinit-builder> Message-ID: <87y26px0yp.fsf@smart-cactus.org> Tom Ellis writes: > If a sponsor (perhaps the HF) could pay for GitLab to host the service > on our behalf would that be helpful? I don't know whether GHC > development relies deeply on some aspect of our self-hosted setup. > (I suspect it does because otherwise we'd likely be using a free > GitLab tier for open source organisations, but I thought the question > was worth asking.) > Migrating towards the SaaS offering is indeed quite enticing. However, last time I checked it wasn't clear to me that it was feasible in our case. The problem isn't the cost as we could in principle request Ultimate-level access to the SaaS via GitLab's FOSS program (which is the same program through which we have our current self-hosted license). The original reason was that we needed to patch GitLab during the migration away from Trac to ensure that ticket metadata was faithfully preserved. While at this point we are running a completely unmodified GitLab instance, my understanding is that there are a few sticking points that would make migration to the SaaS difficult: * the default 10 GB storage quota is extremely small when one considers the size of our CI logs, artifacts, and Docker images * some administrative and debugging tasks sadly become difficult without server access (e.g. I've sometimes found it helpful to look at the server log while debugging CI issues) * Response time of GitLab.com's search functionality has historically been extremely variable, rendering it at times unusable. I'm not sure whether this has improved recently. The first point is especially concerning and has been the primary source of our troubles in self-hosting. As long as we don't run out of storage, GitLab administration tends to be a very minor time commitment (an hour or so a month dealing with spam and upgrading). Thankfully, after today I think we have sufficiently over-provisioned to avoid any future storage issues for the foreseeable future. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From Gergo.Erdi at sc.com Tue Oct 19 01:57:27 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 19 Oct 2021 01:57:27 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: Main.hs Type: application/octet-stream Size: 8895 bytes Desc: Main.hs URL: From simonpj at microsoft.com Tue Oct 19 07:53:36 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 19 Oct 2021 07:53:36 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. When I run it I get simonpj at MSRC-3645512:~/tmp$ ./gergo Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings So now I’m stuck again. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 19 October 2021 02:57 To: Simon Peyton Jones ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Tue Oct 19 08:03:02 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 19 Oct 2021 08:03:02 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm ~/prog/ghc/_build/stage1/lib/$i; done mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do ./hadrian/build-stack _build/stage1/lib/$i; done | Successfully generated _build/stage1/lib/settings. Build completed in 0.41s | Copy file: llvm-passes => _build/stage1/lib/llvm-passes Build completed in 0.40s | Copy file: llvm-targets => _build/stage1/lib/llvm-targets Build completed in 0.52s From: Simon Peyton Jones Sent: Tuesday, October 19, 2021 3:54 PM To: Erdi, Gergo ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. When I run it I get simonpj at MSRC-3645512:~/tmp$ ./gergo Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings So now I’m stuck again. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 02:57 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Oct 19 08:08:24 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 19 Oct 2021 08:08:24 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: Yes I have a full build. No it was not built with Hadrian. I did not realise that your system relied not only on GHC as a library, but also on the build system that you use to build GHC. I guess I can try that, but probably not today. But what is “settings”? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 19 October 2021 09:03 To: Simon Peyton Jones ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm ~/prog/ghc/_build/stage1/lib/$i; done mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do ./hadrian/build-stack _build/stage1/lib/$i; done | Successfully generated _build/stage1/lib/settings. Build completed in 0.41s | Copy file: llvm-passes => _build/stage1/lib/llvm-passes Build completed in 0.40s | Copy file: llvm-targets => _build/stage1/lib/llvm-targets Build completed in 0.52s From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 3:54 PM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. When I run it I get simonpj at MSRC-3645512:~/tmp$ ./gergo Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings So now I’m stuck again. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 02:57 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From Gergo.Erdi at sc.com Tue Oct 19 08:35:33 2021 From: Gergo.Erdi at sc.com (Erdi, Gergo) Date: Tue, 19 Oct 2021 08:35:33 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: PUBLIC PUBLIC “settings”? Honestly, I have no idea. GHC looks at these files in the directory passed to runGhc, and in my local setup I have some convoluted ghc-lib-based system to persist these files and also the base package.db into a Stack/cabal-installable package, but these are only needed for environments where there’s no bona-fide GHC build directory. I am sure even without Hadrian, you should have these files somewhere under your build directory, since otherwise the same same runGhc function (used inside the GHC executable as well…) wouldn’t work. Maybe someone else with non-Hadrian knowledge can tell you where these files are put in the non-Hadrian build. From: Simon Peyton Jones Sent: Tuesday, October 19, 2021 4:08 PM To: Erdi, Gergo ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) Yes I have a full build. No it was not built with Hadrian. I did not realise that your system relied not only on GHC as a library, but also on the build system that you use to build GHC. I guess I can try that, but probably not today. But what is “settings”? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 09:03 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm ~/prog/ghc/_build/stage1/lib/$i; done mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do ./hadrian/build-stack _build/stage1/lib/$i; done | Successfully generated _build/stage1/lib/settings. Build completed in 0.41s | Copy file: llvm-passes => _build/stage1/lib/llvm-passes Build completed in 0.40s | Copy file: llvm-targets => _build/stage1/lib/llvm-targets Build completed in 0.52s From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 3:54 PM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. When I run it I get simonpj at MSRC-3645512:~/tmp$ ./gergo Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings So now I’m stuck again. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 02:57 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Tue Oct 19 18:05:33 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 19 Oct 2021 14:05:33 -0400 Subject: Cmm comments are not Haddock comments---should this change? Message-ID: <20211019180533.D273C2C2F4A@homedog.cs.tufts.edu> The definitions of the Cmm data structures are richly commented in the source code, but the comments are not Haddock comments, so the information doesn't make it into the Haddock documentation. As I refresh my memory about Cmm, I'm thinking of converting the existing comments to Haddock comments. The only downside I can think of is that the Haddock pages may appear more cluttered. Is there any reason I should refrain? Norman From nr at cs.tufts.edu Tue Oct 19 18:33:03 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 19 Oct 2021 14:33:03 -0400 Subject: Cmm comments are not Haddock comments---should this change? In-Reply-To: <20211019180533.D273C2C2F4A@homedog.cs.tufts.edu> (sfid-H-20211019-140538-+42.00-1@multi.osbf.lua) References: <20211019180533.D273C2C2F4A@homedog.cs.tufts.edu> (sfid-H-20211019-140538-+42.00-1@multi.osbf.lua) Message-ID: <20211019183303.E5A0B2C2F4A@homedog.cs.tufts.edu> > As I refresh my memory about Cmm, I'm thinking of converting the > existing comments to Haddock comments. The only downside I can think > of is that the Haddock pages may appear more cluttered. > Is there any reason I should refrain? After sending email, I realized that I should make an issue. It's #20528. https://gitlab.haskell.org/ghc/ghc/-/issues/20528 Norman From simonpj at microsoft.com Wed Oct 20 07:16:10 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 20 Oct 2021 07:16:10 +0000 Subject: Cmm comments are not Haddock comments---should this change? In-Reply-To: <20211019180533.D273C2C2F4A@homedog.cs.tufts.edu> References: <20211019180533.D273C2C2F4A@homedog.cs.tufts.edu> Message-ID: Sounds like a good idea to me. I think `foo` works as we as @foo@ in Haddock comments, and is a whole lot less obtrusive when looking at the comments in their non-typeset form (which is all I ever do). Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) | -----Original Message----- | From: ghc-devs On Behalf Of Norman | Ramsey | Sent: 19 October 2021 19:06 | To: ghc-devs at haskell.org | Subject: Cmm comments are not Haddock comments---should this change? | | The definitions of the Cmm data structures are richly commented in the | source code, but the comments are not Haddock comments, so the | information doesn't make it into the Haddock documentation. | | As I refresh my memory about Cmm, I'm thinking of converting the | existing comments to Haddock comments. The only downside I can think | of is that the Haddock pages may appear more cluttered. | Is there any reason I should refrain? | | | Norman | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C001a611e1b154df0c32d | 08d9932b367b%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637702637000 | 557769%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000&sdata=lgB5GeTImvl5mMDzgzQy2UD4X | %2F3Qf0d1lopgGdiVsxI%3D&reserved=0 From matthewtpickering at gmail.com Wed Oct 20 10:59:14 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 20 Oct 2021 11:59:14 +0100 Subject: Another hadrian option you might want to use Message-ID: Hi, A recent change in the testsuite meant that we now running the haddock tests with hadrian, this means that haddocks for ghc/base get rebuilt if you modify anything in the compiler. This can decrease interaction speed. To disable the documentation tests from running use --docs=none This is similar to the flag which already skips performance tests: --skip-perf Cheers, Matt From alfredo.dinapoli at gmail.com Thu Oct 21 06:23:11 2021 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Thu, 21 Oct 2021 08:23:11 +0200 Subject: Another hadrian option you might want to use In-Reply-To: References: Message-ID: Hello Matthew, Perhaps it would be too niche of a resource, but what about collecting these options either in a Wiki page in GHC or maybe a short blog post on your website (if that's not the case already)? I personally use `--flavour=default+no_profiled_libs+omit_pragmas` all the time with Hadrian these days once you made me discover that magic incantation, but I am essentially relying on my bash history or my search capabilities within this mailing list. I could imagine how other people might have missed your original email, and it would be great if we could have this shared somewhere in a more discoverable way. Alfredo On Wed, 20 Oct 2021 at 12:59, Matthew Pickering wrote: > Hi, > > A recent change in the testsuite meant that we now running the haddock > tests with hadrian, this means that haddocks for ghc/base get rebuilt > if you modify anything in the compiler. > > This can decrease interaction speed. To disable the documentation > tests from running use > > --docs=none > > This is similar to the flag which already skips performance tests: > > --skip-perf > > Cheers, > > Matt > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Oct 21 08:59:48 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 21 Oct 2021 08:59:48 +0000 Subject: Gitlab Message-ID: Is it just me, or is Gitlab offline again? I'm getting error code 500. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) -------------- next part -------------- An HTML attachment was scrubbed... URL: From sam.derbyshire at gmail.com Thu Oct 21 09:03:55 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Thu, 21 Oct 2021 11:03:55 +0200 Subject: Gitlab In-Reply-To: References: Message-ID: It's working for me at the moment. Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Thu Oct 21 09:04:19 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Thu, 21 Oct 2021 10:04:19 +0100 Subject: Gitlab In-Reply-To: References: Message-ID: Working for me. Matt On Thu, Oct 21, 2021 at 10:01 AM Simon Peyton Jones via ghc-devs wrote: > > Is it just me, or is Gitlab offline again? I’m getting error code 500. > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Oct 21 09:07:26 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 21 Oct 2021 10:07:26 +0100 Subject: Gitlab In-Reply-To: References: Message-ID: <20211021090726.GW22523@cloudinit-builder> On Thu, Oct 21, 2021 at 08:59:48AM +0000, Simon Peyton Jones via ghc-devs wrote: > Is it just me, or is Gitlab offline again? I'm getting error code 500. I just checked the following, which all work fine: * Navigate to https://gitlab.haskell.org/ghc/haddock (in Firefox) * git clone https://gitlab.haskell.org/ghc/haddock.git /tmp/haddock * git clone git at gitlab.haskell.org:ghc/haddock.git /tmp/haddock-2 Simon, can you give more precise details about the problem you are experiencing? Tom From sam.derbyshire at gmail.com Thu Oct 21 09:10:38 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Thu, 21 Oct 2021 11:10:38 +0200 Subject: Gitlab In-Reply-To: <20211021090726.GW22523@cloudinit-builder> References: <20211021090726.GW22523@cloudinit-builder> Message-ID: I'm also getting error 500 now. Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk Thu Oct 21 09:15:10 2021 From: tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 21 Oct 2021 10:15:10 +0100 Subject: Gitlab In-Reply-To: References: <20211021090726.GW22523@cloudinit-builder> Message-ID: <20211021091510.GA9145@cloudinit-builder> On Thu, Oct 21, 2021 at 11:10:38AM +0200, Sam Derbyshire wrote: > I'm also getting error 500 now. Where? When visiting gitlab.haskell.org in your browser or when using git on the command line? Tom From sam.derbyshire at gmail.com Thu Oct 21 09:17:01 2021 From: sam.derbyshire at gmail.com (Sam Derbyshire) Date: Thu, 21 Oct 2021 11:17:01 +0200 Subject: Gitlab In-Reply-To: <20211021091510.GA9145@cloudinit-builder> References: <20211021090726.GW22523@cloudinit-builder> <20211021091510.GA9145@cloudinit-builder> Message-ID: Yes, when visiting gitlab.haskell.org, but it seems to be OK again now. Sam -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Oct 21 10:30:45 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 21 Oct 2021 10:30:45 +0000 Subject: Gitlab In-Reply-To: <20211021090726.GW22523@cloudinit-builder> References: <20211021090726.GW22523@cloudinit-builder> Message-ID: It started working again, a few mins after it stopped working. I was getting consistent Error 500, then started being OK. Strange. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) | -----Original Message----- | From: ghc-devs On Behalf Of Tom Ellis | Sent: 21 October 2021 10:07 | To: ghc-devs at haskell.org | Subject: Re: Gitlab | | On Thu, Oct 21, 2021 at 08:59:48AM +0000, Simon Peyton Jones via ghc- | devs wrote: | > Is it just me, or is Gitlab offline again? I'm getting error code | 500. | | I just checked the following, which all work fine: | | * Navigate to | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl | ab.haskell.org%2Fghc%2Fhaddock&data=04%7C01%7Csimonpj%40microsoft. | com%7Ca9e47aca8f374f19f98008d994723bf3%7C72f988bf86f141af91ab2d7cd011d | b47%7C1%7C0%7C637704041244004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wL | jAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000&sdata | =QF5AEHaNFKWepD697Jvtz1pr70%2B4GaK4RuKTBSaFgLI%3D&reserved=0 (in | Firefox) | | * git clone | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl | ab.haskell.org%2Fghc%2Fhaddock.git&data=04%7C01%7Csimonpj%40micros | oft.com%7Ca9e47aca8f374f19f98008d994723bf3%7C72f988bf86f141af91ab2d7cd | 011db47%7C1%7C0%7C637704041244004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiM | C4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000&s | data=zPu4532C%2FsdgdIyZu2ExDvFHBTNtsd7IQfMhsmV47EM%3D&reserved=0 | /tmp/haddock | | * git clone git at gitlab.haskell.org:ghc/haddock.git /tmp/haddock-2 | | Simon, can you give more precise details about the problem you are | experiencing? | | Tom | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7Ca9e47aca8f374f19f980 | 08d994723bf3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637704041244 | 004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000&sdata=CC%2F0tJSLYXL8A763MtT9%2F | Y%2BQG7PL3cSngakqUcFUDes%3D&reserved=0 From ben at smart-cactus.org Thu Oct 21 13:57:26 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 21 Oct 2021 09:57:26 -0400 Subject: Gitlab In-Reply-To: References: <20211021090726.GW22523@cloudinit-builder> Message-ID: <87ee8ewkel.fsf@smart-cactus.org> Simon Peyton Jones via ghc-devs writes: > It started working again, a few mins after it stopped working. I was > getting consistent Error 500, then started being OK. > > Strange. > Indeed there was a misconfiguration that caused this sort of intermittent failure which I have now fixed. Apoloegies for the inconvenience! Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From carter.schonwald at gmail.com Thu Oct 21 14:09:22 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 21 Oct 2021 10:09:22 -0400 Subject: Another hadrian option you might want to use In-Reply-To: References: Message-ID: A cheat sheet on the wiki linking to different build system tricks is a great idea! On Thu, Oct 21, 2021 at 2:23 AM Alfredo Di Napoli < alfredo.dinapoli at gmail.com> wrote: > Hello Matthew, > > Perhaps it would be too niche of a resource, but what about collecting > these options either in a Wiki page in GHC or maybe a short blog post on > your website (if that's not the case already)? I personally use > `--flavour=default+no_profiled_libs+omit_pragmas` all the time with Hadrian > these days once you made me discover that magic incantation, but I am > essentially relying on my bash history or my search capabilities within > this mailing list. > > I could imagine how other people might have missed your original email, > and it would be great if we could have this shared somewhere in a more > discoverable way. > > Alfredo > > > On Wed, 20 Oct 2021 at 12:59, Matthew Pickering < > matthewtpickering at gmail.com> wrote: > >> Hi, >> >> A recent change in the testsuite meant that we now running the haddock >> tests with hadrian, this means that haddocks for ghc/base get rebuilt >> if you modify anything in the compiler. >> >> This can decrease interaction speed. To disable the documentation >> tests from running use >> >> --docs=none >> >> This is similar to the flag which already skips performance tests: >> >> --skip-perf >> >> Cheers, >> >> Matt >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Thu Oct 21 15:17:41 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Thu, 21 Oct 2021 11:17:41 -0400 Subject: Another hadrian option you might want to use In-Reply-To: (sfid-H-20211021-095847-+129.36-1@multi.osbf.lua) References: (sfid-H-20211021-095847-+129.36-1@multi.osbf.lua) Message-ID: <20211021151741.C7F812C307E@homedog.cs.tufts.edu> > Perhaps it would be too niche of a resource, but what about collecting > these options either in a Wiki page in GHC In the interests of "done now is better than perfect later," I have added a note about these options to https://gitlab.haskell.org/ghc/ghc/-/wikis/building/hadrian. This is where the command > `--flavour=default+no_profiled_libs+omit_pragmas` is already documented. Norman From simonpj at microsoft.com Fri Oct 22 11:11:50 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 22 Oct 2021 11:11:50 +0000 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: I’m out of cycles. Do please open a ticket. You are more likely to get attention that way. Matthew: maybe you can help with reproducing this? SImon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo Sent: 19 October 2021 09:36 To: Simon Peyton Jones ; 'Matthew Pickering' Cc: Montelatici, Raphael Laurent ; 'GHC' Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC “settings”? Honestly, I have no idea. GHC looks at these files in the directory passed to runGhc, and in my local setup I have some convoluted ghc-lib-based system to persist these files and also the base package.db into a Stack/cabal-installable package, but these are only needed for environments where there’s no bona-fide GHC build directory. I am sure even without Hadrian, you should have these files somewhere under your build directory, since otherwise the same same runGhc function (used inside the GHC executable as well…) wouldn’t work. Maybe someone else with non-Hadrian knowledge can tell you where these files are put in the non-Hadrian build. From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 4:08 PM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) Yes I have a full build. No it was not built with Hadrian. I did not realise that your system relied not only on GHC as a library, but also on the build system that you use to build GHC. I guess I can try that, but probably not today. But what is “settings”? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 09:03 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm ~/prog/ghc/_build/stage1/lib/$i; done mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do ./hadrian/build-stack _build/stage1/lib/$i; done | Successfully generated _build/stage1/lib/settings. Build completed in 0.41s | Copy file: llvm-passes => _build/stage1/lib/llvm-passes Build completed in 0.40s | Copy file: llvm-targets => _build/stage1/lib/llvm-targets Build completed in 0.52s From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 3:54 PM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. When I run it I get simonpj at MSRC-3645512:~/tmp$ ./gergo Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings So now I’m stuck again. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 19 October 2021 02:57 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM To: Erdi, Gergo >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) I could not compile Main.hs: ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc Gergo.hs:4:1: error: Could not find module ‘Paths_ghc_lib’ Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 4 | import qualified Paths_ghc_lib as GHC | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ simonpj at MSRC-3645512:~/tmp$ Would you like to open a ticket rather than do this by email? Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: Erdi, Gergo > Sent: 15 October 2021 05:35 To: Simon Peyton Jones >; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent >; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b seq = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b $dmseq = \ (@(m :: * -> *)) ($dMonad [Occ=Once1] :: Monad m) (@a) (@b) (ma [Occ=Once1] :: m a) (mb [Occ=OnceL1] :: m b) -> let { sat_ss0 [Occ=Once1] :: a -> m b [LclId] sat_ss0 = \ _ [Occ=Dead] -> mb } in bind @m $dMonad @a @b ma sat_ss0 $fMonadIO :: Monad IO $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; foo :: IO () foo = seq @IO $fMonadIO @() @() ioA ioA If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Fri Oct 22 13:29:51 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Fri, 22 Oct 2021 14:29:51 +0100 Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: Hi, If there is a ticket then I can look into it next week. Cheers, Matt On Fri, Oct 22, 2021 at 12:11 PM Simon Peyton Jones wrote: > > I’m out of cycles. Do please open a ticket. You are more likely to get attention that way. > > > > Matthew: maybe you can help with reproducing this? > > > SImon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: Erdi, Gergo > Sent: 19 October 2021 09:36 > To: Simon Peyton Jones ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > PUBLIC > > > > PUBLIC > > > > “settings”? Honestly, I have no idea. GHC looks at these files in the directory passed to runGhc, and in my local setup I have some convoluted ghc-lib-based system to persist these files and also the base package.db into a Stack/cabal-installable package, but these are only needed for environments where there’s no bona-fide GHC build directory. > > > > I am sure even without Hadrian, you should have these files somewhere under your build directory, since otherwise the same same runGhc function (used inside the GHC executable as well…) wouldn’t work. Maybe someone else with non-Hadrian knowledge can tell you where these files are put in the non-Hadrian build. > > > > From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 4:08 PM > To: Erdi, Gergo ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > Yes I have a full build. No it was not built with Hadrian. I did not realise that your system relied not only on GHC as a library, but also on the build system that you use to build GHC. > > > > I guess I can try that, but probably not today. But what is “settings”? > > > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: Erdi, Gergo > Sent: 19 October 2021 09:03 > To: Simon Peyton Jones ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > PUBLIC > > > > PUBLIC > > > > Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: > > > > mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm ~/prog/ghc/_build/stage1/lib/$i; done > > mi at localhost[ghc] $ for i in settings llvm-passes llvm-targets; do ./hadrian/build-stack _build/stage1/lib/$i; done > > | Successfully generated _build/stage1/lib/settings. > > Build completed in 0.41s > > > > | Copy file: llvm-passes => _build/stage1/lib/llvm-passes > > Build completed in 0.40s > > > > | Copy file: llvm-targets => _build/stage1/lib/llvm-targets > > Build completed in 0.52s > > > > > > > > From: Simon Peyton Jones > Sent: Tuesday, October 19, 2021 3:54 PM > To: Erdi, Gergo ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 > > > > Plenty of tickets turn out to be non-bugs. But they are still searchable, and form a permanent record that may help others, perhaps in unexpected ways. So I encourage you to do so. > > > > I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ as a command line argument. > > > > When I run it I get > > simonpj at MSRC-3645512:~/tmp$ ./gergo > > Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings > > > > So now I’m stuck again. > > > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: Erdi, Gergo > Sent: 19 October 2021 02:57 > To: Simon Peyton Jones ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > PUBLIC > > > > PUBLIC > > > > Thanks for looking into this! > > > > `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `libDir` to your environment. > > > > As for opening a ticket – a big part of the problem is that I don’t even know yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket would even be for – “I’m using the GHC API wrongly” is not a strong bug report 😊 > > > > > > From: Simon Peyton Jones > Sent: Saturday, October 16, 2021 12:52 AM > To: Erdi, Gergo ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > I could not compile Main.hs: > > ~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc > > > > Gergo.hs:4:1: error: > > Could not find module ‘Paths_ghc_lib’ > > Use -v (or `:set -v` in ghci) to see a list of the files searched for. > > | > > 4 | import qualified Paths_ghc_lib as GHC > > | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ > > simonpj at MSRC-3645512:~/tmp$ > > > > Would you like to open a ticket rather than do this by email? > > > Simon > > > > PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) > > > > From: Erdi, Gergo > Sent: 15 October 2021 05:35 > To: Simon Peyton Jones ; 'Matthew Pickering' > Cc: Montelatici, Raphael Laurent ; 'GHC' > Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) > > > > PUBLIC > > > > PUBLIC > > > > OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): > > > > seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b > > seq > > = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) -> > > case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV } > > > > $dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b > > $dmseq > > = \ (@(m :: * -> *)) > > ($dMonad [Occ=Once1] :: Monad m) > > (@a) > > (@b) > > (ma [Occ=Once1] :: m a) > > (mb [Occ=OnceL1] :: m b) -> > > let { > > sat_ss0 [Occ=Once1] :: a -> m b > > [LclId] > > sat_ss0 = \ _ [Occ=Dead] -> mb } in > > bind @m $dMonad @a @b ma sat_ss0 > > > > $fMonadIO :: Monad IO > > $fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq; > > > > $fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b > > $fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b; > > > > foo :: IO () > > foo = seq @IO $fMonadIO @() @() ioA ioA > > > > If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just doesn’t *do* anything. > > > > > > > This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations > > Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm > > Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. > > Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. > > Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. > > Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. > > > This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations > > Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm > > Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. > > Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. > > Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. > > Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. > > > This email and any attachments are confidential and may also be privileged. If you are not the intended recipient, please delete all copies and notify the sender immediately. You may wish to refer to the incorporation details of Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at https: //www.sc.com/en/our-locations > > Where you have a Financial Markets relationship with Standard Chartered PLC, Standard Chartered Bank and their subsidiaries (the "Group"), information on the regulatory standards we adhere to and how it may affect you can be found in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm > > Insofar as this communication is not sent by the Global Research team and contains any market commentary, the market commentary has been prepared by the sales and/or trading desk of Standard Chartered Bank or its affiliate. It is not and does not constitute research material, independent research, recommendation or financial advice. Any market commentary is for information purpose only and shall not be relied on for any other purpose and is subject to the relevant disclaimers available at https: //www.sc.com/en/regulatory-disclosures/#market-disclaimer. > > Insofar as this communication is sent by the Global Research team and contains any research materials prepared by members of the team, the research material is for information purpose only and shall not be relied on for any other purpose, and is subject to the relevant disclaimers available at https: //research.sc.com/research/api/application/static/terms-and-conditions. > > Insofar as this e-mail contains the term sheet for a proposed transaction, by responding affirmatively to this e-mail, you agree that you have understood the terms and conditions in the attached term sheet and evaluated the merits and risks of the transaction. We may at times also request you to sign the term sheet to acknowledge the same. > > Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for important information with respect to derivative products. From facundo.dominguez at tweag.io Fri Oct 22 16:16:28 2021 From: facundo.dominguez at tweag.io (=?UTF-8?Q?Dom=C3=ADnguez=2C_Facundo?=) Date: Fri, 22 Oct 2021 13:16:28 -0300 Subject: Meaning of -i and -hidir Message-ID: Dear devs, I'm confused about the meaning of -hidir and -i. Here's my experiment with both ghc-9.2.0 and ghc-8.10.4. > $ find > ./Main.hs > ./lib/Lib.hs > > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib > > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main > > Main.hs:3:1: error: > Bad interface file: hidir_Main/Lib.hi > hidir_Main/Lib.hi: openBinaryFile: does not exist (No such file or directory) > | > 3 | import Lib > | ^^^^^^^^^^ If I only use -hidir, it still fails with another error > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib > > Main.hs:7:29: error: Variable not in scope: f > | > 7 | main = print $(runIO (print f) >> [| True |]) > | ^ If I use both -i and -hidir pointing to the same folder, then it works! > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib Now, is this behavior a bug or a feature? And if it is a bug, what is the expected behavior? Programs copied below. Thank you! Facundo > $ cat lib/Lib.hs > module Lib where > > f :: Int > f = 1 > > $ cat Main.hs > {-# LANGUAGE TemplateHaskell #-} > > import Lib > import Language.Haskell.TH > > main :: IO () > main = print $(runIO (print f) >> [| True |]) -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Fri Oct 22 19:30:11 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Fri, 22 Oct 2021 15:30:11 -0400 Subject: how to find Zero-boot packages with Hadrian? Message-ID: <20211022193011.DC4D92C2E97@homedog.cs.tufts.edu> What is the Hadrian equivalent of make show VALUE=BOOT_PKGS ? From nr at cs.tufts.edu Fri Oct 22 19:49:46 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Fri, 22 Oct 2021 15:49:46 -0400 Subject: build-system design document: how relevant is it now? Message-ID: <20211022194946.765D42C2E97@homedog.cs.tufts.edu> I'm trawling the GHC wiki looking for things that will help me understand how the build system works and what might need to change for cross-compilation. I stumbled across https://gitlab.haskell.org/ghc/ghc/-/wikis/design/build-system which git helpfully tells me dates from 2008. I assume that none of it is relevant any longer. In its current form, the page seems only likely to confuse future contributors. I'd rather not leave things that way. Does the page have archival value? Is there a directory of legacy pages to which I should move it? Or shall I just delete the current text and replace it with a short note? Or what? Norman From simonpj at microsoft.com Fri Oct 22 20:40:48 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 22 Oct 2021 20:40:48 +0000 Subject: build-system design document: how relevant is it now? In-Reply-To: <20211022194946.765D42C2E97@homedog.cs.tufts.edu> References: <20211022194946.765D42C2E97@homedog.cs.tufts.edu> Message-ID: It's already a sub-tree of "attic" -- ie out of date, retained for archive. The title index is useful: https://gitlab.haskell.org/ghc/ghc/-/wikis/index Maybe "attic" isn't the best name. Maybe each page should have a header saying "Historical value only". But I hate the idea of outright deletion! Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) | -----Original Message----- | From: ghc-devs On Behalf Of Norman | Ramsey | Sent: 22 October 2021 20:50 | To: ghc-devs at haskell.org | Subject: build-system design document: how relevant is it now? | | | I'm trawling the GHC wiki looking for things that will help me | understand how the build system works and what might need to change | for cross-compilation. I stumbled across | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl | ab.haskell.org%2Fghc%2Fghc%2F-%2Fwikis%2Fdesign%2Fbuild- | system&data=04%7C01%7Csimonpj%40microsoft.com%7C4c127b6d7e8f4b6008 | 9708d995953f60%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6377052911 | 25359257%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiL | CJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=e3MIn5ElWrtNmCC9u4uOP%2 | BQGcx4lU%2FFI8QfxQ0%2FbyOM%3D&reserved=0 | which git helpfully tells me dates from 2008. I assume that none of | it is relevant any longer. | | In its current form, the page seems only likely to confuse future | contributors. I'd rather not leave things that way. Does the page | have archival value? Is there a directory of legacy pages to which I | should move it? Or shall I just delete the current text and replace | it with a short note? Or what? | | | Norman | | _______________________________________________ | ghc-devs mailing list | ghc-devs at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail. | haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc- | devs&data=04%7C01%7Csimonpj%40microsoft.com%7C4c127b6d7e8f4b600897 | 08d995953f60%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637705291125 | 359257%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ | BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=m8dQ5eHD%2Ba0FoK9IFXM7z38 | ehaAg75I9wj2ESNQZaJM%3D&reserved=0 From ben at smart-cactus.org Fri Oct 22 21:07:22 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 22 Oct 2021 17:07:22 -0400 Subject: build-system design document: how relevant is it now? In-Reply-To: <20211022194946.765D42C2E97@homedog.cs.tufts.edu> References: <20211022194946.765D42C2E97@homedog.cs.tufts.edu> Message-ID: <871r4cwyyv.fsf@smart-cactus.org> Norman Ramsey writes: > I'm trawling the GHC wiki looking for things that will help > me understand how the build system works and what might need > to change for cross-compilation. I stumbled across > https://gitlab.haskell.org/ghc/ghc/-/wikis/design/build-system > which git helpfully tells me dates from 2008. I assume that > none of it is relevant any longer. > Somewhat surprisingly, the document is still largely accurate. However, I suspect that it is redundant given the rather significant body of build system documentation in the Wiki's Commentary. Ultimately all of this build system documentation will hopefully be obsoleted with the removal of the make build system in favor of Hadrian. It's hard to know what to do in cases like this. There is likely still archival value in this documentation but as archival documentation accrues the signal-to-noise ratio of the entire body of documentation falls. I am hope that we can avoid this in the future by erring towards keeping documentation in the repository, where it is easier to ensure that documentation tracks changes in the implementation that it describes. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From ben at smart-cactus.org Fri Oct 22 21:10:56 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Fri, 22 Oct 2021 17:10:56 -0400 Subject: how to find Zero-boot packages with Hadrian? In-Reply-To: <20211022193011.DC4D92C2E97@homedog.cs.tufts.edu> References: <20211022193011.DC4D92C2E97@homedog.cs.tufts.edu> Message-ID: <87y26kvk8g.fsf@smart-cactus.org> Norman Ramsey writes: > What is the Hadrian equivalent of > > make show VALUE=BOOT_PKGS > I don't believe there is currently a command-line equivalent. The list itself is known as Settings.Default.stage0Packages. What is your use-case? Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From oleg.grenrus at iki.fi Sat Oct 23 09:59:49 2021 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Sat, 23 Oct 2021 12:59:49 +0300 Subject: Meaning of -i and -hidir In-Reply-To: References: Message-ID: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> This looks like a bug. -hidir documentation says > Redirects all generated interface files into ⟨dir⟩, instead of the default. > Please also note that when doing incremental compilation (by ghc --make or ghc -c), this directory is where GHC looks into to find interface files. And documentation for -i doesn't mention looking for interface files. So by doing % ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib % ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Main -ihidir_Lib 1 % ghc odir/Lib.o odir/Main.o -o Demo                                  % ./Demo                                                              True everything compiles, TH is run, and demo works. The result files are % find . . ./Demo ./Main.hs ./hidir_Main ./hidir_Main/Main.dyn_hi ./hidir_Main/Main.hi ./odir ./odir/Main.dyn_o ./odir/Main.o ./odir/Lib.dyn_o ./odir/Lib.o ./hidir_Lib ./hidir_Lib/Lib.dyn_hi ./hidir_Lib/Lib.hi ./lib ./lib/Lib.hs --- The confusing error is caused by Lib module in libiserv: https://hackage.haskell.org/package/libiserv which GHC picks! If we rename your Lib module to Library, the error is way better: Could not find module ‘Library’ I also tried using same -hidir when compiling both modules, then GHC still cannot find the Library interface, even the documentation says it should. Please open a GHC issue at https://gitlab.haskell.org/ghc/ghc/-/issues - Oleg On 22.10.2021 19.16, Domínguez, Facundo wrote: > Dear devs, > > I'm confused about the meaning of -hidir and -i. Here's my experiment > with both ghc-9.2.0 and ghc-8.10.4. > > > $ find > > ./Main.hs > > ./lib/Lib.hs > > > > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib > > > > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main > > > > Main.hs:3:1: error: > >     Bad interface file: hidir_Main/Lib.hi > >         hidir_Main/Lib.hi: openBinaryFile: does not exist (No such > file or directory) > >   | > > 3 | import Lib > >   | ^^^^^^^^^^ > > If I only use -hidir, it still fails with another error > > > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib > > > > Main.hs:7:29: error: Variable not in scope: f > >   | > > 7 | main = print $(runIO (print f) >> [| True |]) > >   |                             ^ > > If I use both -i and -hidir pointing to the same folder, then it works! > > > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib > > Now, is this behavior a bug or a feature? And if it is a bug, what is > the expected behavior? > > Programs copied below. > > Thank you! > Facundo > > > $ cat lib/Lib.hs > > module Lib where > > > > f :: Int > > f = 1 > > > > $ cat Main.hs > > {-# LANGUAGE TemplateHaskell #-} > > > > import Lib > > import Language.Haskell.TH > > > > main :: IO () > > main = print $(runIO (print f) >> [| True |]) > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Oct 23 18:31:19 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 23 Oct 2021 14:31:19 -0400 Subject: Meaning of -i and -hidir In-Reply-To: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: I would assume the -i is for include c header search paths but I could be wrong On Sat, Oct 23, 2021 at 6:00 AM Oleg Grenrus wrote: > This looks like a bug. > > -hidir documentation says > > > Redirects all generated interface files into ⟨dir⟩, instead of the > default. > > Please also note that when doing incremental compilation (by ghc --make > or ghc -c), this directory is where GHC looks into to find interface files. > > And documentation for -i doesn't mention looking for interface files. > > So by doing > > % ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib > % ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Main -ihidir_Lib > 1 > % ghc odir/Lib.o odir/Main.o -o Demo > % ./Demo > True > > everything compiles, TH is run, and demo works. The result files are > > % find . > . > ./Demo > ./Main.hs > ./hidir_Main > ./hidir_Main/Main.dyn_hi > ./hidir_Main/Main.hi > ./odir > ./odir/Main.dyn_o > ./odir/Main.o > ./odir/Lib.dyn_o > ./odir/Lib.o > ./hidir_Lib > ./hidir_Lib/Lib.dyn_hi > ./hidir_Lib/Lib.hi > ./lib > ./lib/Lib.hs > > --- > > The confusing error is caused by Lib module in libiserv: > https://hackage.haskell.org/package/libiserv > which GHC picks! > > If we rename your Lib module to Library, the error is way better: Could > not find module ‘Library’ > > I also tried using same -hidir when compiling both modules, then GHC still > cannot find the Library interface, even the documentation says it should. > > Please open a GHC issue at https://gitlab.haskell.org/ghc/ghc/-/issues > > > > - Oleg > On 22.10.2021 19.16, Domínguez, Facundo wrote: > > Dear devs, > > I'm confused about the meaning of -hidir and -i. Here's my experiment with > both ghc-9.2.0 and ghc-8.10.4. > > > $ find > > ./Main.hs > > ./lib/Lib.hs > > > > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib > > > > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main > > > > Main.hs:3:1: error: > > Bad interface file: hidir_Main/Lib.hi > > hidir_Main/Lib.hi: openBinaryFile: does not exist (No such file > or directory) > > | > > 3 | import Lib > > | ^^^^^^^^^^ > > If I only use -hidir, it still fails with another error > > > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib > > > > Main.hs:7:29: error: Variable not in scope: f > > | > > 7 | main = print $(runIO (print f) >> [| True |]) > > | ^ > > If I use both -i and -hidir pointing to the same folder, then it works! > > > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib > > Now, is this behavior a bug or a feature? And if it is a bug, what is the > expected behavior? > > Programs copied below. > > Thank you! > Facundo > > > $ cat lib/Lib.hs > > module Lib where > > > > f :: Int > > f = 1 > > > > $ cat Main.hs > > {-# LANGUAGE TemplateHaskell #-} > > > > import Lib > > import Language.Haskell.TH > > > > main :: IO () > > main = print $(runIO (print f) >> [| True |]) > > _______________________________________________ > ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sat Oct 23 18:36:30 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 23 Oct 2021 14:36:30 -0400 Subject: Meaning of -i and -hidir In-Reply-To: References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: I would expect that to be -I and for -i to specify module paths (which might well mean .hi). On Sat, Oct 23, 2021 at 2:32 PM Carter Schonwald wrote: > I would assume the -i is for include c header search paths but I could be > wrong > > On Sat, Oct 23, 2021 at 6:00 AM Oleg Grenrus wrote: > >> This looks like a bug. >> >> -hidir documentation says >> >> > Redirects all generated interface files into ⟨dir⟩, instead of the >> default. >> > Please also note that when doing incremental compilation (by ghc --make >> or ghc -c), this directory is where GHC looks into to find interface files. >> >> And documentation for -i doesn't mention looking for interface files. >> >> So by doing >> >> % ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >> % ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Main -ihidir_Lib >> 1 >> % ghc odir/Lib.o odir/Main.o -o Demo >> % ./Demo >> True >> >> everything compiles, TH is run, and demo works. The result files are >> >> % find . >> . >> ./Demo >> ./Main.hs >> ./hidir_Main >> ./hidir_Main/Main.dyn_hi >> ./hidir_Main/Main.hi >> ./odir >> ./odir/Main.dyn_o >> ./odir/Main.o >> ./odir/Lib.dyn_o >> ./odir/Lib.o >> ./hidir_Lib >> ./hidir_Lib/Lib.dyn_hi >> ./hidir_Lib/Lib.hi >> ./lib >> ./lib/Lib.hs >> >> --- >> >> The confusing error is caused by Lib module in libiserv: >> https://hackage.haskell.org/package/libiserv >> which GHC picks! >> >> If we rename your Lib module to Library, the error is way better: Could >> not find module ‘Library’ >> >> I also tried using same -hidir when compiling both modules, then GHC >> still cannot find the Library interface, even the documentation says it >> should. >> >> Please open a GHC issue at https://gitlab.haskell.org/ghc/ghc/-/issues >> >> >> >> - Oleg >> On 22.10.2021 19.16, Domínguez, Facundo wrote: >> >> Dear devs, >> >> I'm confused about the meaning of -hidir and -i. Here's my experiment >> with both ghc-9.2.0 and ghc-8.10.4. >> >> > $ find >> > ./Main.hs >> > ./lib/Lib.hs >> > >> > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >> > >> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main >> > >> > Main.hs:3:1: error: >> > Bad interface file: hidir_Main/Lib.hi >> > hidir_Main/Lib.hi: openBinaryFile: does not exist (No such file >> or directory) >> > | >> > 3 | import Lib >> > | ^^^^^^^^^^ >> >> If I only use -hidir, it still fails with another error >> >> > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib >> > >> > Main.hs:7:29: error: Variable not in scope: f >> > | >> > 7 | main = print $(runIO (print f) >> [| True |]) >> > | ^ >> >> If I use both -i and -hidir pointing to the same folder, then it works! >> >> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib >> >> Now, is this behavior a bug or a feature? And if it is a bug, what is the >> expected behavior? >> >> Programs copied below. >> >> Thank you! >> Facundo >> >> > $ cat lib/Lib.hs >> > module Lib where >> > >> > f :: Int >> > f = 1 >> > >> > $ cat Main.hs >> > {-# LANGUAGE TemplateHaskell #-} >> > >> > import Lib >> > import Language.Haskell.TH >> > >> > main :: IO () >> > main = print $(runIO (print f) >> [| True |]) >> >> _______________________________________________ >> ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -- brandon s allbery kf8nh allbery.b at gmail.com -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sat Oct 23 20:25:26 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 23 Oct 2021 16:25:26 -0400 Subject: Meaning of -i and -hidir In-Reply-To: References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: Could be! I’m far from a computer much of this week On Sat, Oct 23, 2021 at 2:36 PM Brandon Allbery wrote: > I would expect that to be -I and for -i to specify module paths (which > might well mean .hi). > > On Sat, Oct 23, 2021 at 2:32 PM Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> I would assume the -i is for include c header search paths but I could be >> wrong >> >> On Sat, Oct 23, 2021 at 6:00 AM Oleg Grenrus wrote: >> >>> This looks like a bug. >>> >>> -hidir documentation says >>> >>> > Redirects all generated interface files into ⟨dir⟩, instead of the >>> default. >>> > Please also note that when doing incremental compilation (by ghc >>> --make or ghc -c), this directory is where GHC looks into to find interface >>> files. >>> >>> And documentation for -i doesn't mention looking for interface files. >>> >>> So by doing >>> >>> % ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >>> % ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Main -ihidir_Lib >>> 1 >>> % ghc odir/Lib.o odir/Main.o -o Demo >>> % ./Demo >>> True >>> >>> everything compiles, TH is run, and demo works. The result files are >>> >>> % find . >>> . >>> ./Demo >>> ./Main.hs >>> ./hidir_Main >>> ./hidir_Main/Main.dyn_hi >>> ./hidir_Main/Main.hi >>> ./odir >>> ./odir/Main.dyn_o >>> ./odir/Main.o >>> ./odir/Lib.dyn_o >>> ./odir/Lib.o >>> ./hidir_Lib >>> ./hidir_Lib/Lib.dyn_hi >>> ./hidir_Lib/Lib.hi >>> ./lib >>> ./lib/Lib.hs >>> >>> --- >>> >>> The confusing error is caused by Lib module in libiserv: >>> https://hackage.haskell.org/package/libiserv >>> which GHC picks! >>> >>> If we rename your Lib module to Library, the error is way better: Could >>> not find module ‘Library’ >>> >>> I also tried using same -hidir when compiling both modules, then GHC >>> still cannot find the Library interface, even the documentation says it >>> should. >>> >>> Please open a GHC issue at https://gitlab.haskell.org/ghc/ghc/-/issues >>> >>> >>> >>> - Oleg >>> On 22.10.2021 19.16, Domínguez, Facundo wrote: >>> >>> Dear devs, >>> >>> I'm confused about the meaning of -hidir and -i. Here's my experiment >>> with both ghc-9.2.0 and ghc-8.10.4. >>> >>> > $ find >>> > ./Main.hs >>> > ./lib/Lib.hs >>> > >>> > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >>> > >>> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main >>> > >>> > Main.hs:3:1: error: >>> > Bad interface file: hidir_Main/Lib.hi >>> > hidir_Main/Lib.hi: openBinaryFile: does not exist (No such >>> file or directory) >>> > | >>> > 3 | import Lib >>> > | ^^^^^^^^^^ >>> >>> If I only use -hidir, it still fails with another error >>> >>> > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib >>> > >>> > Main.hs:7:29: error: Variable not in scope: f >>> > | >>> > 7 | main = print $(runIO (print f) >> [| True |]) >>> > | ^ >>> >>> If I use both -i and -hidir pointing to the same folder, then it works! >>> >>> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib >>> >>> Now, is this behavior a bug or a feature? And if it is a bug, what is >>> the expected behavior? >>> >>> Programs copied below. >>> >>> Thank you! >>> Facundo >>> >>> > $ cat lib/Lib.hs >>> > module Lib where >>> > >>> > f :: Int >>> > f = 1 >>> > >>> > $ cat Main.hs >>> > {-# LANGUAGE TemplateHaskell #-} >>> > >>> > import Lib >>> > import Language.Haskell.TH >>> > >>> > main :: IO () >>> > main = print $(runIO (print f) >> [| True |]) >>> >>> _______________________________________________ >>> ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > > > -- > brandon s allbery kf8nh > allbery.b at gmail.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fryguybob at gmail.com Sat Oct 23 20:34:52 2021 From: fryguybob at gmail.com (Ryan Yates) Date: Sat, 23 Oct 2021 16:34:52 -0400 Subject: Meaning of -i and -hidir In-Reply-To: References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: The behavior of `-hidir` and `-i` changed in response to this issue: https://gitlab.haskell.org/ghc/ghc/-/issues/16500 We just ran into this and I think the change is unfortunate. I don't think `-hidir` (a flag about output) should override the input search flag. I would like it to at least merge the two so it searches both the `-hidir` and the `-i`s rather than overriding. Reverting the change would be fine too (I think) because you can always specify the same path as `-hidir` and `-i`. As it is now, you can control *both* the input and the output. On Sat, Oct 23, 2021 at 4:26 PM Carter Schonwald wrote: > Could be! I’m far from a computer much of this week > > On Sat, Oct 23, 2021 at 2:36 PM Brandon Allbery > wrote: > >> I would expect that to be -I and for -i to specify module paths (which >> might well mean .hi). >> >> On Sat, Oct 23, 2021 at 2:32 PM Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >>> I would assume the -i is for include c header search paths but I >>> could be wrong >>> >>> On Sat, Oct 23, 2021 at 6:00 AM Oleg Grenrus >>> wrote: >>> >>>> This looks like a bug. >>>> >>>> -hidir documentation says >>>> >>>> > Redirects all generated interface files into ⟨dir⟩, instead of the >>>> default. >>>> > Please also note that when doing incremental compilation (by ghc >>>> --make or ghc -c), this directory is where GHC looks into to find interface >>>> files. >>>> >>>> And documentation for -i doesn't mention looking for interface files. >>>> >>>> So by doing >>>> >>>> % ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >>>> % ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Main -ihidir_Lib >>>> 1 >>>> % ghc odir/Lib.o odir/Main.o -o Demo >>>> % ./Demo >>>> True >>>> >>>> everything compiles, TH is run, and demo works. The result files are >>>> >>>> % find . >>>> . >>>> ./Demo >>>> ./Main.hs >>>> ./hidir_Main >>>> ./hidir_Main/Main.dyn_hi >>>> ./hidir_Main/Main.hi >>>> ./odir >>>> ./odir/Main.dyn_o >>>> ./odir/Main.o >>>> ./odir/Lib.dyn_o >>>> ./odir/Lib.o >>>> ./hidir_Lib >>>> ./hidir_Lib/Lib.dyn_hi >>>> ./hidir_Lib/Lib.hi >>>> ./lib >>>> ./lib/Lib.hs >>>> >>>> --- >>>> >>>> The confusing error is caused by Lib module in libiserv: >>>> https://hackage.haskell.org/package/libiserv >>>> which GHC picks! >>>> >>>> If we rename your Lib module to Library, the error is way better: Could >>>> not find module ‘Library’ >>>> >>>> I also tried using same -hidir when compiling both modules, then GHC >>>> still cannot find the Library interface, even the documentation says it >>>> should. >>>> >>>> Please open a GHC issue at https://gitlab.haskell.org/ghc/ghc/-/issues >>>> >>>> >>>> >>>> - Oleg >>>> On 22.10.2021 19.16, Domínguez, Facundo wrote: >>>> >>>> Dear devs, >>>> >>>> I'm confused about the meaning of -hidir and -i. Here's my experiment >>>> with both ghc-9.2.0 and ghc-8.10.4. >>>> >>>> > $ find >>>> > ./Main.hs >>>> > ./lib/Lib.hs >>>> > >>>> > $ ghc -dynamic-too -c lib/Lib.hs -odir odir -hidir hidir_Lib >>>> > >>>> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Main >>>> > >>>> > Main.hs:3:1: error: >>>> > Bad interface file: hidir_Main/Lib.hi >>>> > hidir_Main/Lib.hi: openBinaryFile: does not exist (No such >>>> file or directory) >>>> > | >>>> > 3 | import Lib >>>> > | ^^^^^^^^^^ >>>> >>>> If I only use -hidir, it still fails with another error >>>> >>>> > $ ghc -dynamic-too -c Main.hs -odir odir -hidir hidir_Lib >>>> > >>>> > Main.hs:7:29: error: Variable not in scope: f >>>> > | >>>> > 7 | main = print $(runIO (print f) >> [| True |]) >>>> > | ^ >>>> >>>> If I use both -i and -hidir pointing to the same folder, then it works! >>>> >>>> > $ ghc -dynamic-too -c Main.hs -odir odir -ihidir_Lib -hidir hidir_Lib >>>> >>>> Now, is this behavior a bug or a feature? And if it is a bug, what is >>>> the expected behavior? >>>> >>>> Programs copied below. >>>> >>>> Thank you! >>>> Facundo >>>> >>>> > $ cat lib/Lib.hs >>>> > module Lib where >>>> > >>>> > f :: Int >>>> > f = 1 >>>> > >>>> > $ cat Main.hs >>>> > {-# LANGUAGE TemplateHaskell #-} >>>> > >>>> > import Lib >>>> > import Language.Haskell.TH >>>> > >>>> > main :: IO () >>>> > main = print $(runIO (print f) >> [| True |]) >>>> >>>> _______________________________________________ >>>> ghc-devs mailing listghc-devs at haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>>> >>>> _______________________________________________ >>>> ghc-devs mailing list >>>> ghc-devs at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>>> >>> _______________________________________________ >>> ghc-devs mailing list >>> ghc-devs at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >>> >> >> >> -- >> brandon s allbery kf8nh >> allbery.b at gmail.com >> > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Sun Oct 24 02:17:28 2021 From: qdunkan at gmail.com (Evan Laforge) Date: Sat, 23 Oct 2021 19:17:28 -0700 Subject: Meaning of -i and -hidir In-Reply-To: References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: The issue uses consistency with -odir and -hieDir as a rationalization. I think it's not quite right because inputs can have a search path while outputs don't, but if it is true that -odir simultaneously sets the output and input dir for `*.o`, that seems confusing too. Shouldn't -odir set *only* output, and all inputs should either be lumped under the `-i` search path, or even split up into separate flags as outputs are? If you are building in --make mode then you will naturally want to read .o files from the last place you wrote them, but in that case you can explicitly say so. I'm not actually advocating for this since I don't have a use for it at the moment, and I don't want to potentially break every single user of ghc --make, but it seemed to me that the argument for consistency could run the other direction. I think this issue is coming up due to a mismatch between the traditional Make style builds which assume a single mutable input and output directory, and the newer functional / hermetic style builds which require immutable inputs and a mutable output. It's a familiar concept, just transposed to the file system! From a.pelenitsyn at gmail.com Sun Oct 24 20:19:46 2021 From: a.pelenitsyn at gmail.com (Artem Pelenitsyn) Date: Sun, 24 Oct 2021 15:19:46 -0500 Subject: Another hadrian option you might want to use In-Reply-To: <20211021151741.C7F812C307E@homedog.cs.tufts.edu> References: <20211021151741.C7F812C307E@homedog.cs.tufts.edu> Message-ID: Is there a reason to not add (some of) these to the flavor=Quick? — Best, Artem On Thu, Oct 21, 2021 at 11:18 AM Norman Ramsey wrote: > > Perhaps it would be too niche of a resource, but what about collecting > > these options either in a Wiki page in GHC > > In the interests of "done now is better than perfect later," I have > added a note about these options to > https://gitlab.haskell.org/ghc/ghc/-/wikis/building/hadrian. > This is where the command > > > `--flavour=default+no_profiled_libs+omit_pragmas` > > is already documented. > > > Norman > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gergo at erdi.hu Mon Oct 25 09:50:46 2021 From: gergo at erdi.hu (=?ISO-8859-2?Q?=C9RDI_Gerg=F5?=) Date: Mon, 25 Oct 2021 17:50:46 +0800 (+08) Subject: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*) In-Reply-To: References: Message-ID: On Fri, 22 Oct 2021, Matthew Pickering wrote: > If there is a ticket then I can look into it next week. Thanks! I've added it as https://gitlab.haskell.org/ghc/ghc/-/issues/20556 From nr at cs.tufts.edu Tue Oct 26 16:11:02 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 26 Oct 2021 12:11:02 -0400 Subject: How to close an issue that won't happen? Message-ID: <20211026161102.E04A32C1AEE@homedog.cs.tufts.edu> Issue #20370 is not going to happen. I have added a comment of explanation, and it's time for me to close the issue. What label, if any, should I put on the issue to indicate that it describes a direction we've decided not to pursue? Norman From ben at smart-cactus.org Tue Oct 26 16:27:48 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Tue, 26 Oct 2021 12:27:48 -0400 Subject: How to close an issue that won't happen? In-Reply-To: <20211026161102.E04A32C1AEE@homedog.cs.tufts.edu> References: <20211026161102.E04A32C1AEE@homedog.cs.tufts.edu> Message-ID: <87mtmvvjin.fsf@smart-cactus.org> Norman Ramsey writes: > Issue #20370 is not going to happen. I have added a comment of explanation, > and it's time for me to close the issue. What label, if any, should I > put on the issue to indicate that it describes a direction we've decided > not to pursue? > No need to add a label. Just close with a comment explaining the reason for closure. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From nr at cs.tufts.edu Tue Oct 26 21:31:38 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Tue, 26 Oct 2021 17:31:38 -0400 Subject: how to find Zero-boot packages with Hadrian? In-Reply-To: <87y26kvk8g.fsf@smart-cactus.org> (sfid-H-20211022-171159-+48.10-1@multi.osbf.lua) References: <20211022193011.DC4D92C2E97@homedog.cs.tufts.edu> <87y26kvk8g.fsf@smart-cactus.org> (sfid-H-20211022-171159-+48.10-1@multi.osbf.lua) Message-ID: <20211026213138.3D8B62C1AE4@homedog.cs.tufts.edu> > Norman Ramsey writes: > > > What is the Hadrian equivalent of > > > > make show VALUE=BOOT_PKGS > > > I don't believe there is currently a command-line equivalent. The list > itself is known as Settings.Default.stage0Packages. > > What is your use-case? I was updating the Commentary (commentary/libraries.md) and found this text: To find out which packages are currently zero-boot packages, do the following in a GHC build: ```wiki $ make show VALUE=BOOT_PKGS ``` Since `make` will go away eventually, I wanted to tell people how to discover zero-boot packages using Hadrian. Norman From lazyswamp at gmail.com Tue Oct 26 22:45:41 2021 From: lazyswamp at gmail.com (Kwanghoon Choi) Date: Tue, 26 Oct 2021 23:45:41 +0100 Subject: How to use Lexer.lexer to produce closing braces as well? In-Reply-To: References: Message-ID: Thank you Edward for your reply. It took some time for me to understand a formal description (translation function L) of the Haskell layout rule in Section 10.3 of Haskell 2010 language report. :) I myself tried to write an example with the Haskell layout rule for me to understand it. I am sharing this for those who are curious about the Haskell layout rules. - http://lazyswamp.blogspot.com/2021/10/on-haskell-layout-rule.html Kwanghoon PS. To be honest, however, I still don't know how Haskell parser (Parser.y) and lexer (Lexer.x) interact with each other to implement the following rule on the insertion of a closing brace on a parse error. [Sec. 10.3] - L (t : ts) (m : ms) = } : (L (t : ts) ms) if m /= 0 and parse-error(t) It seems that Happy's error recover is relevant to the interaction via a production rule: [ Parser.y ] - close :: { () } : vccurly { () } -- context popped in lexer. | error {% popContext } Is it enough for a Haskell lexer just to pop the top context? It is not clear to me how vccurly is inserted just by having such a production rule and an error recovery. On Wed, 18 Aug 2021 at 17:05, Edward Kmett wrote: > Unfortunately, the current parsing rules for Haskell aren't fully > phase-separable like this. > > If you look at the rules for Layout token insertion in the Haskell report > the 9th rule requires that in the event the parser encounters a parse > error it should insert a virtual close brace and continue on! > > Otherwise you couldn't parse things like *let **{** foo = bar **}** in > baz *where the {}'s are virtual without reframing *let* and *in* as a > different kind of paired opening and closing brace or using other hacks in > the grammar. It is quite difficult to hack around all the ways parses can > go wrong. > > The main downside this has from a language standpoint is you simply can't > properly lex Haskell without more or less fully parsing Haskell. > > -Edward > > On Wed, Aug 18, 2021 at 7:22 AM Kwanghoon Choi > wrote: > >> >> Hi, >> >> I have recently been playing with GHC's Lexer.lexer in the ghc-parser-lib >> package. >> >> Given >> >> module HelloWorld where >> >> main = putStrLn "Hello World!\n" >> >> it produces >> >> stack exec -- lexer-exe ./examples/HelloWorld.hs >> Lexing&Parsing: ./examples/HelloWorld.hs >> module at (1, 1): module >> CONID at (1, 8): CONID >> where at (1, 19): where >> vocurly at (3, 1): vocurly <==== { is inserted automatically!! >> VARID at (3, 1): VARID >> = at (3, 6): = >> VARID at (3, 8): VARID >> STRING at (3, 17): STRING >> ; at (4, 1): ; >> >> By the example above, the lexer automatically inserts an opening brace >> (i.e. vocurly) right after 'where'. But it does not insert a matching >> closing brace (i.e., vccurly), which would lead to a failure in parsing a >> list of tokens produced by the lexer. >> >> My question is how to use the GHC lexer to produce closing braces as >> well. >> >> All my code is available >> - https://github.com/kwanghoon/hslexer >> >> To save your time, the relevant part of the code is as follows: >> >> In app/HaskellLexer.hs, >> >> singleHaskellToken :: P (Located Token) >> singleHaskellToken = >> Lexer.lexer False >> (\locatedToken -> P (\pstate -> POk pstate locatedToken)) >> >> tokInfos :: [Terminal Token] -> P (Line, Column, [Terminal Token]) >> tokInfos s = do >> locatedToken <- singleHaskellToken >> case locatedToken of >> L srcspan ITeof -> >> let (start_line, start_col, end_line, end_col) = >> srcSpanToLineCol srcspan in >> return (end_line, end_col, s) >> >> L srcspan tok -> >> let (start_line, start_col, end_line, end_col) = >> srcSpanToLineCol srcspan in >> tokInfos (Terminal (fromToken tok) start_line start_col (Just >> tok) : s) >> >> Thanks in advance >> >> Best regards, >> >> Kwanghoon >> >> >> >> >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.redelings at gmail.com Wed Oct 27 13:36:01 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Wed, 27 Oct 2021 09:36:01 -0400 Subject: Resources on how to implement (Haskell 98) kind checking? In-Reply-To: <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> References: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> Message-ID: <1a0bee00-145f-2330-ab9d-0d51cf49dd48@gmail.com> Hi Richard, Many thanks for the hints! On 10/15/21 1:37 PM, Richard Eisenberg wrote: > >>> I can see two ways to proceed: >>> >>> i) First determine the kinds of all the data types, classes, and >>> type synonyms.  Then perform a second pass over each type or class >>> to determine the kinds of type variables (in class methods) that are >>> not type class parameters. > > This won't work. > > class C a where >   meth :: a b -> b Int > > You have to know the kind of local b to learn the kind of > class-variable a. So you have to do it all at once. I was doing it all at once -- but I wasn't sure how to export the information about 'b' from the procedure.  (After you record the kinds of the typecons like C, I believe the different typecons in the recursive group become separable.) I presume (in retrospect) that GHC modifies the declaration to record the kind of b, and then re-walks the declaration to substitute kind variables later? >> >> iii) Represent kinds with modifiable variables. Substitution can be >> implemented by modifying kind variables in-place.  This is (I think) >> called "zonking" in the GHC sources. > > I don't really see the difference between (ii) and (iii). Maybe (ii) > records the kinds in a table somewhere, while (iii) records them "in" > the kind variables themselves, but that's not so different, I think. Yeah, that is a good point.  That clarified for me what GHC is doing. > >> This solves a small mystery for me, since I previously thought that >> zonking was just replacing remaining kind variables with '*'.  And >> indeed this seems to be an example of zonking, but not what zonking >> is (I think). > > We can imagine that, instead of mutation, we build a substitution > mapping unification variables to types (or kinds). This would be > stored just as a simple mapping or dictionary structure. No mutation. > As we learn about a unification variable, we just add to the mapping. > If we did this, zonking would be the act of applying the substitution, > replacing known unification variables with their values. It just so > happens that GHC builds a mapping by using mutable cells in memory, > but that's just an implementation detail: zonking is still just > applying the substitution. OK, that makes sense.  I'll start with the mapping approach, and then consider optimizing things later. > Zonking does /not/ replace anything with *. Well, functions that have > "zonk" in their name may do this. But it is not really logically part > of the zonking operation. If you like, you can pretend that, after > zonking a program, we take a separate pass replacing any yet-unfilled > kind-level unification variables with *. Sometimes, this is called > "zapping" in GHC, I believe. Yes, I was definitely confusing zonking and zapping.  (Wow, lots of fun names here!) > Zonking is a bit laborious to implement, but not painful. Laborious, > because it requires a full pass over the AST. Not painful, because all > it's trying to do is replace type/kind variables with substitutions: > each individual piece of the puzzle is quite simple. This was quite helpful -- I think I was trying to somehow avoid a separate pass over the AST. But if that is a difficulty on the right road, I will just go for it. -BenRI -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.redelings at gmail.com Wed Oct 27 13:42:33 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Wed, 27 Oct 2021 09:42:33 -0400 Subject: Resources on how to implement (Haskell 98) kind checking? In-Reply-To: <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> References: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> Message-ID: <271b9c8e-9683-f1ea-0c91-7256938e441d@gmail.com> Oh, I forgot to add, would it make sense to put some of the information I discovered about implementing kind checking into the wiki somewhere?  I am mostly thinking of a sequence of steps like: 1. Divide class, data/newtype, type synonym, and instance declarations into recursive groups. 1a) Record for each group which LOCAL typecons are mentioned in the declaration 1b) ... etc 2. Infer kinds within a recursive group 2a) Treat type classes as having kind k1 -> k2 -> ... -> kn -> Constraint 2b) Begin by recording a kind k1 -> k2 -> ... -> kn -> Constraint/* for each typecon 2c) etc... 2d) Substitute kind variables (zonking) 2e) Substitute * for remaining kind variables (zapping) 3. ... I am not actually sure what to write yet, the above is just an illustration. It might also help to reference the relevant papers (mostly the PolyKinds paper), and maybe also to mention papers like the THIH paper that don't actually implement kind checking. -BenRI On 10/15/21 1:37 PM, Richard Eisenberg wrote: > > >> On Oct 14, 2021, at 11:59 AM, Benjamin Redelings >> wrote: >> >> >> I asked about this on Haskell-Cafe, and was recommended to ask here >> instead.  Any help is much appreciated! >> > > I saw your post over there, but haven't had time to respond.... but > this retelling of the story makes it easier to respond, so I'll do so > here. > >> * The PolyKinds paper was the most helpful thing I've found, but it >> doesn't cover type classes. I'm also not sure that all implementers >> can follow algorithm descriptions that are laid out as inference >> rules, but maybe that could be fixed with a few hints about how to >> run the rules in reverse.  Also, in practice I think an implementer >> would want to follow GHC in specifying the initial kind of a data >> type as k1 -> k2 -> ... kn -> *. >> > > What is unique about type classes? It seems like you're worried about > locally quantified type variables in method types, but (as far as kind > inference is concerned) those are very much like existential variables > in data constructors. So perhaps take the bit about existential > variables from the PolyKinds part of that paper and combine it with > the Haskell98 part. > > It's true that many implementors may find the notation in that paper > to be a barrier, but you just have to read the rules clockwise, > starting from the bottom left and ending on the bottom right. :) >> >> >> 2. The following question (which I have maybe kind of answered now, >> but could use more advice on) is an example of what I am hoping such >> documentation would explain: >> >>> Q: How do you handle type variables that are present in class >>> methods, but are not type class parameters? If there are multiple >>> types/classes in a single recursive group, the kind of such type >>> variables might not be fully resolved until a later type-or-class is >>> processed.  Is there a recommended approach? >>> >>> I can see two ways to proceed: >>> >>> i) First determine the kinds of all the data types, classes, and >>> type synonyms.  Then perform a second pass over each type or class >>> to determine the kinds of type variables (in class methods) that are >>> not type class parameters. > > This won't work. > > class C a where >   meth :: a b -> b Int > > You have to know the kind of local b to learn the kind of > class-variable a. So you have to do it all at once. > >>> >>> ii) Alternatively, record the kind of each type variable as it is >>> encountered -- even though such kinds may contain unification kind >>> variables.  After visiting all types-or-classes in the recursive >>> group, replace any kind variables with their definition, or with a * >>> if there is no definition. >>> >>> I've currently implement approach i), which requires doing kind >>> inference on class methods twice. >>> >> Further investigation revealed that GHC takes yet another approach (I >> think): >> >> iii) Represent kinds with modifiable variables. Substitution can be >> implemented by modifying kind variables in-place.  This is (I think) >> called "zonking" in the GHC sources. > > I don't really see the difference between (ii) and (iii). Maybe (ii) > records the kinds in a table somewhere, while (iii) records them "in" > the kind variables themselves, but that's not so different, I think. > >> >> This solves a small mystery for me, since I previously thought that >> zonking was just replacing remaining kind variables with '*'.  And >> indeed this seems to be an example of zonking, but not what zonking >> is (I think). > > We can imagine that, instead of mutation, we build a substitution > mapping unification variables to types (or kinds). This would be > stored just as a simple mapping or dictionary structure. No mutation. > As we learn about a unification variable, we just add to the mapping. > If we did this, zonking would be the act of applying the substitution, > replacing known unification variables with their values. It just so > happens that GHC builds a mapping by using mutable cells in memory, > but that's just an implementation detail: zonking is still just > applying the substitution. > > Zonking does /not/ replace anything with *. Well, functions that have > "zonk" in their name may do this. But it is not really logically part > of the zonking operation. If you like, you can pretend that, after > zonking a program, we take a separate pass replacing any yet-unfilled > kind-level unification variables with *. Sometimes, this is called > "zapping" in GHC, I believe. > >> >> Zonking looks painful to implement, but approach (i) might require >> multiple passes over types to update the kind of type variables, >> which might be worse... > > Zonking is a bit laborious to implement, but not painful. Laborious, > because it requires a full pass over the AST. Not painful, because all > it's trying to do is replace type/kind variables with substitutions: > each individual piece of the puzzle is quite simple. > > I hope this is helpful! > Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.redelings at gmail.com Wed Oct 27 13:54:17 2021 From: benjamin.redelings at gmail.com (Benjamin Redelings) Date: Wed, 27 Oct 2021 09:54:17 -0400 Subject: Output language of typechecking pass? Message-ID: Hi,     I have been looking for info on what actually comes out of the type-checking pass in GHC.  This is mostly because it seems like the "Type classes in Haskell" paper implements both type checking and translation to dictionary-passing in one pass, whereas it seems like GHC separates this into (i) type checking and (ii) desugaring. Questions: 1. It seems like this separation is actually necessary, in order to apply generalization only to let arguments written by the programmer, and not to let bindings introduced during desugaring. Is that right? 2. Does the output of type checking contain type lambdas? 3. Does the type checking pass determine where to add dictionary arguments? 4. Are there any other resources I should be looking at? I am confused about #3, because the `-ddump-tc` output doesn't seem to show any type dictionaries in function bodies themselves, but it does seem to contain some kind of info about dictionaries as "evidence" -- but I am not sure what "evidence" is, or how it links into the AST for a function body.  I did briefly look at `-ddump-tc-ast`, but not in detail yet. -BenRI From facundo.dominguez at tweag.io Wed Oct 27 17:28:30 2021 From: facundo.dominguez at tweag.io (=?UTF-8?Q?Dom=C3=ADnguez=2C_Facundo?=) Date: Wed, 27 Oct 2021 14:28:30 -0300 Subject: Meaning of -i and -hidir In-Reply-To: References: <4b323729-a9ac-1fab-35fc-5ef26eea5780@iki.fi> Message-ID: Thanks everyone for your thoughts. I have opened an issue here: https://gitlab.haskell.org/ghc/ghc/-/issues/20569 Best, Facundo On Sat, Oct 23, 2021 at 11:18 PM Evan Laforge wrote: > The issue uses consistency with -odir and -hieDir as a > rationalization. I think it's not quite right because inputs can have > a search path while outputs don't, but if it is true that -odir > simultaneously sets the output and input dir for `*.o`, that seems > confusing too. Shouldn't -odir set *only* output, and all inputs > should either be lumped under the `-i` search path, or even split up > into separate flags as outputs are? If you are building in --make > mode then you will naturally want to read .o files from the last place > you wrote them, but in that case you can explicitly say so. I'm not > actually advocating for this since I don't have a use for it at the > moment, and I don't want to potentially break every single user of ghc > --make, but it seemed to me that the argument for consistency could > run the other direction. > > I think this issue is coming up due to a mismatch between the > traditional Make style builds which assume a single mutable input and > output directory, and the newer functional / hermetic style builds > which require immutable inputs and a mutable output. It's a familiar > concept, just transposed to the file system! > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Wed Oct 27 18:59:46 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Wed, 27 Oct 2021 18:59:46 +0000 Subject: Output language of typechecking pass? In-Reply-To: References: Message-ID: <010f017cc31f63bb-475c1cf3-17f9-4904-9d14-45fbe88cbe51-000000@us-east-2.amazonses.com> > On Oct 27, 2021, at 9:54 AM, Benjamin Redelings wrote: > > Hi, > > I have been looking for info on what actually comes out of the type-checking pass in GHC. This is mostly because it seems like the "Type classes in Haskell" paper implements both type checking and translation to dictionary-passing in one pass, whereas it seems like GHC separates this into (i) type checking and (ii) desugaring. This is correct: GHC takes two different passes to do this work. The big reason is around error messages: we want to have the code that the user wrote when reporting error messages. Since errors arise during type-checking, we thus want the output of the type checker to look like what the user wrote. > > Questions: > > 1. It seems like this separation is actually necessary, in order to apply generalization only to let arguments written by the programmer, and not to let bindings introduced during desugaring. Is that right? I don't think so. That is, if we did it all in one pass, I still think we could get generalization right. > > 2. Does the output of type checking contain type lambdas? Yes. See below. > > 3. Does the type checking pass determine where to add dictionary arguments? Yes. See below. > > 4. Are there any other resources I should be looking at? Yes. You want to enable -fprint-typechecker-elaboration (and possible -fprint-explicit-coercions). With the former, you get to see all this stuff you're looking for. It's normally suppressed so that the output resembles the user's code. I hope this helps! Richard From lists at richarde.dev Wed Oct 27 19:15:02 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Wed, 27 Oct 2021 19:15:02 +0000 Subject: Resources on how to implement (Haskell 98) kind checking? In-Reply-To: <1a0bee00-145f-2330-ab9d-0d51cf49dd48@gmail.com> References: <8d91ada9-9f6c-0500-86a4-2a40b8da1a88@gmail.com> <010f017c8507c42b-13b49b21-3b8e-4a8d-93b6-56c60f61ed60-000000@us-east-2.amazonses.com> <1a0bee00-145f-2330-ab9d-0d51cf49dd48@gmail.com> Message-ID: <010f017cc32d5cc3-b9d8afaf-205c-48f3-be8b-05257dd7557d-000000@us-east-2.amazonses.com> > On Oct 27, 2021, at 9:36 AM, Benjamin Redelings wrote: >> >> This won't work. >> >> class C a where >> meth :: a b -> b Int >> >> You have to know the kind of local b to learn the kind of class-variable a. So you have to do it all at once. > I was doing it all at once -- but I wasn't sure how to export the information about 'b' from the procedure. (After you record the kinds of the typecons like C, I believe the different typecons in the recursive group become separable.) > > I presume (in retrospect) that GHC modifies the declaration to record the kind of b, and then re-walks the declaration to substitute kind variables later? > That would be smart, but it's not what GHC does. Instead, GHC first says (a :: kappa), for a fresh unification variable kappa. Then, GHC determines (b :: Type -> Type) and thus unifies kappa := (Type -> Type) -> Type. GHC then *throws away* the information about b. (See the `_ <- ...` at https://gitlab.haskell.org/ghc/ghc/-/blob/638f65482ca5265c268aa97abfcc14cdc27e46ba/compiler/GHC/Tc/Gen/HsType.hs#L388) Having now determined conclusively what the kind of `a` is, GHC will later re-check the kind of the type of meth, recording it for good. > But if that is a difficulty on the right road, I will just go for it. > If zonking is a difficulty, there's probably something wrong somewhere. Lengthy, yes, but not difficult. If you're using Data.Data, I imagine you could implement zonking with just the right use of Data.Generics.Schemes.everywhere. > Oh, I forgot to add, would it make sense to put some of the information I discovered about implementing kind checking into the wiki somewhere? > This is an excellent idea, but I'll counterpropose that you write this in a Note. Indeed, Note [Kind checking for type and class decls] in GHC.Tc.TyCl is probably meant to be the Note you're looking for, but it's too short. Feel free to flesh it out with all of these details. Then, make sure that the functions that implement the details refer to the Note (and vice versa). This will help it to stay up-to-date -- much more so than putting it in the wiki. > It might also help to reference the relevant papers (mostly the PolyKinds paper), and maybe also to mention papers like the THIH paper that don't actually implement kind checking. > Yes, refer to papers. But please do use their proper names (years and conference names are also helpful). It actually took some inference for me to figure out what the "PolyKinds paper" was in your emails. (The paper that proposes the extension that became PolyKinds is "Giving Haskell a Promotion", TLDI'12, and the paper that describes its extension to work more generally is "System FC with Explicit Kind Equality", ICFP'13. I thought you were referring to one of these -- not to "Kind Inference for Datatypes".) Thanks! Richard > -BenRI > > On 10/15/21 1:37 PM, Richard Eisenberg wrote: >> >> >>> On Oct 14, 2021, at 11:59 AM, Benjamin Redelings > wrote: >>> >>> I asked about this on Haskell-Cafe, and was recommended to ask here instead. Any help is much appreciated! >>> >> >> I saw your post over there, but haven't had time to respond.... but this retelling of the story makes it easier to respond, so I'll do so here. >> >>> * The PolyKinds paper was the most helpful thing I've found, but it doesn't cover type classes. I'm also not sure that all implementers can follow algorithm descriptions that are laid out as inference rules, but maybe that could be fixed with a few hints about how to run the rules in reverse. Also, in practice I think an implementer would want to follow GHC in specifying the initial kind of a data type as k1 -> k2 -> ... kn -> *. >>> >> >> What is unique about type classes? It seems like you're worried about locally quantified type variables in method types, but (as far as kind inference is concerned) those are very much like existential variables in data constructors. So perhaps take the bit about existential variables from the PolyKinds part of that paper and combine it with the Haskell98 part. >> >> It's true that many implementors may find the notation in that paper to be a barrier, but you just have to read the rules clockwise, starting from the bottom left and ending on the bottom right. :) >>> >>> 2. The following question (which I have maybe kind of answered now, but could use more advice on) is an example of what I am hoping such documentation would explain: >>> >>> >>>> Q: How do you handle type variables that are present in class methods, but are not type class parameters? If there are multiple types/classes in a single recursive group, the kind of such type variables might not be fully resolved until a later type-or-class is processed. Is there a recommended approach? >>>> >>>> I can see two ways to proceed: >>>> >>>> i) First determine the kinds of all the data types, classes, and type synonyms. Then perform a second pass over each type or class to determine the kinds of type variables (in class methods) that are not type class parameters. >> >> This won't work. >> >> class C a where >> meth :: a b -> b Int >> >> You have to know the kind of local b to learn the kind of class-variable a. So you have to do it all at once. >> >>>> >>>> ii) Alternatively, record the kind of each type variable as it is encountered -- even though such kinds may contain unification kind variables. After visiting all types-or-classes in the recursive group, replace any kind variables with their definition, or with a * if there is no definition. >>>> >>>> I've currently implement approach i), which requires doing kind inference on class methods twice. >>>> >>> Further investigation revealed that GHC takes yet another approach (I think): >>> >>> iii) Represent kinds with modifiable variables. Substitution can be implemented by modifying kind variables in-place. This is (I think) called "zonking" in the GHC sources. >> >> I don't really see the difference between (ii) and (iii). Maybe (ii) records the kinds in a table somewhere, while (iii) records them "in" the kind variables themselves, but that's not so different, I think. >> >>> >>> This solves a small mystery for me, since I previously thought that zonking was just replacing remaining kind variables with '*'. And indeed this seems to be an example of zonking, but not what zonking is (I think). >> >> We can imagine that, instead of mutation, we build a substitution mapping unification variables to types (or kinds). This would be stored just as a simple mapping or dictionary structure. No mutation. As we learn about a unification variable, we just add to the mapping. If we did this, zonking would be the act of applying the substitution, replacing known unification variables with their values. It just so happens that GHC builds a mapping by using mutable cells in memory, but that's just an implementation detail: zonking is still just applying the substitution. >> >> Zonking does not replace anything with *. Well, functions that have "zonk" in their name may do this. But it is not really logically part of the zonking operation. If you like, you can pretend that, after zonking a program, we take a separate pass replacing any yet-unfilled kind-level unification variables with *. Sometimes, this is called "zapping" in GHC, I believe. >> >>> >>> Zonking looks painful to implement, but approach (i) might require multiple passes over types to update the kind of type variables, which might be worse... >> >> Zonking is a bit laborious to implement, but not painful. Laborious, because it requires a full pass over the AST. Not painful, because all it's trying to do is replace type/kind variables with substitutions: each individual piece of the puzzle is quite simple. >> >> I hope this is helpful! >> Richard > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Wed Oct 27 20:49:14 2021 From: ben at well-typed.com (Ben Gamari) Date: Wed, 27 Oct 2021 16:49:14 -0400 Subject: Running GHC in GHCi Message-ID: <87wnlytcqw.fsf@smart-cactus.org> Hi all, Today I verified that with Luite's recent work on the interpreter it is now possible to run GHC entirely within GHCi (when bootstrapping from GHC 9.2). Behold: ``` $ # First we must remove -fno-code from hadrian/ghci $ git apply < import Main λ> :set args -B/opt/exp/ghc/ghc-landing/_build/stage1/lib --version λ> :trace main The Glorious Glasgow Haskell Compilation System, version 9.3.20211027 λ> :set args -B/opt/exp/ghc/ghc-landing/_build/stage1/lib HelloWorld.hs λ> main [1 of 1] Compiling Main ( HelloWorld.hs, HelloWorld.o ) Linking HelloWorld ... λ> :! ./HelloWorld "Hello World!" ``` Surprisingly, performance isn't even horrible, taking only a few seconds to compile "hello world". Sadly, `:trace` doesn't quite work yet on `main`: ``` λ> :trace main *** Exception: ModBreaks.modBreaks_array not initialised CallStack (from HasCallStack): error, called at compiler/GHC/ByteCode/Types.hs:231:24 in ghc:GHC.ByteCode.Types ``` I've opened #20570 to track this issue. Fixing it would allow breakpoints and the like to be used on GHC. Anyways, I found this quite exciting. Perhaps this will spur more contributors to take an interest in GHCi. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From ben at well-typed.com Thu Oct 28 00:08:26 2021 From: ben at well-typed.com (Ben Gamari) Date: Wed, 27 Oct 2021 20:08:26 -0400 Subject: Running GHC in GHCi In-Reply-To: <87wnlytcqw.fsf@smart-cactus.org> References: <87wnlytcqw.fsf@smart-cactus.org> Message-ID: <87tuh2t3j1.fsf@smart-cactus.org> Ben Gamari writes: > Hi all, > > Today I verified that with Luite's recent work on the interpreter it is > now possible to run GHC entirely within GHCi (when bootstrapping from > GHC 9.2). > > ... > I have fixed the break-array issue noted in the above message in !6848. It is now possible to use `:trace` on GHC itself: $ hadrian/ghci GHCi, version 9.2.1: https://www.haskell.org/ghc/ :? for help . . . λ> import Main λ> :set args -B/opt/exp/ghc/ghc-landing/_build/stage1/lib Hi.hs -v3 -fforce-recomp λ> :set -fbreak-on-error λ> :trace main Glasgow Haskell Compiler, Version 9.3.20211027, stage 1 booted by GHC version 9.2.1 ^CStopped in , _exception :: e = _ [] λ> :hist -1 : fromException (/opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24) -2 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) -3 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) -4 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:64-78) -5 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:18-25) -6 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) -7 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) -8 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-43) -9 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-13) -10 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-25) -11 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:(252,3)-(253,54)) -12 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-78) -13 : compare (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:42:23-49) -14 : fs_sbs (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) -15 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:44-53) -16 : fs_sbs (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) -17 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:31-40) -18 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:3-54) -19 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) -20 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) ... [] λ> :back Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24 _result :: Maybe GHC.Utils.Panic.Plain.PlainGhcException e :: SomeAsyncException [-1: /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24] λ> :back Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10 _result :: Int uniq :: Int [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> uniq 603980920 [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> :back Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35 _result :: ModuleName mod :: ModuleName [-3: /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35] λ> mod ModuleName "GHC.Tc.Solver.Canonical" et cetera -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From b at chreekat.net Thu Oct 28 04:25:46 2021 From: b at chreekat.net (Bryan Richter) Date: Thu, 28 Oct 2021 07:25:46 +0300 Subject: Running GHC in GHCi In-Reply-To: <87tuh2t3j1.fsf@smart-cactus.org> References: <87wnlytcqw.fsf@smart-cactus.org> <87tuh2t3j1.fsf@smart-cactus.org> Message-ID: That's very exciting! On Thu, 28 Oct 2021, 3.08 Ben Gamari, wrote: > Ben Gamari writes: > > > Hi all, > > > > Today I verified that with Luite's recent work on the interpreter it is > > now possible to run GHC entirely within GHCi (when bootstrapping from > > GHC 9.2). > > > > ... > > > I have fixed the break-array issue noted in the above message in !6848. > It is now possible to use `:trace` on GHC itself: > > > $ hadrian/ghci > GHCi, version 9.2.1: https://www.haskell.org/ghc/ :? for help > . > . > . > λ> import Main > λ> :set args -B/opt/exp/ghc/ghc-landing/_build/stage1/lib Hi.hs -v3 > -fforce-recomp > λ> :set -fbreak-on-error > λ> :trace main > Glasgow Haskell Compiler, Version 9.3.20211027, stage 1 booted by GHC > version 9.2.1 > ^CStopped in , > _exception :: e = _ > [] λ> :hist > -1 : fromException > (/opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24) > -2 : uniq > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) > -3 : moduleNameFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) > -4 : stableModuleNameCmp > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:64-78) > -5 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:18-25) > -6 : uniq > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) > -7 : moduleNameFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) > -8 : stableModuleNameCmp > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-43) > -9 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-13) > -10 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-25) > -11 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:(252,3)-(253,54)) > -12 : stableModuleNameCmp > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-78) > -13 : compare > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:42:23-49) > -14 : fs_sbs > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) > -15 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:44-53) > -16 : fs_sbs > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) > -17 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:31-40) > -18 : lexicalCompareFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:3-54) > -19 : uniq > (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) > -20 : moduleNameFS > (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) > ... > [] λ> :back > Logged breakpoint at > /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24 > _result :: Maybe GHC.Utils.Panic.Plain.PlainGhcException > e :: SomeAsyncException > [-1: /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24] λ> > :back > Logged breakpoint at > /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10 > _result :: Int > uniq :: Int > [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> > uniq > 603980920 > [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> > :back > Logged breakpoint at > /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35 > _result :: ModuleName > mod :: ModuleName > [-3: /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35] > λ> mod > ModuleName "GHC.Tc.Solver.Canonical" > > et cetera > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Thu Oct 28 07:52:18 2021 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Thu, 28 Oct 2021 08:52:18 +0100 Subject: Running GHC in GHCi In-Reply-To: References: <87wnlytcqw.fsf@smart-cactus.org> <87tuh2t3j1.fsf@smart-cactus.org> Message-ID: Looks good Ben. Would it be good to add a target to hadrian which builds just the right dependencies for this to work? and then deals with setting options such as -B as well. Matt On Thu, Oct 28, 2021 at 5:26 AM Bryan Richter wrote: > > That's very exciting! > > On Thu, 28 Oct 2021, 3.08 Ben Gamari, wrote: >> >> Ben Gamari writes: >> >> > Hi all, >> > >> > Today I verified that with Luite's recent work on the interpreter it is >> > now possible to run GHC entirely within GHCi (when bootstrapping from >> > GHC 9.2). >> > >> > ... >> > >> I have fixed the break-array issue noted in the above message in !6848. >> It is now possible to use `:trace` on GHC itself: >> >> >> $ hadrian/ghci >> GHCi, version 9.2.1: https://www.haskell.org/ghc/ :? for help >> . >> . >> . >> λ> import Main >> λ> :set args -B/opt/exp/ghc/ghc-landing/_build/stage1/lib Hi.hs -v3 -fforce-recomp >> λ> :set -fbreak-on-error >> λ> :trace main >> Glasgow Haskell Compiler, Version 9.3.20211027, stage 1 booted by GHC version 9.2.1 >> ^CStopped in , >> _exception :: e = _ >> [] λ> :hist >> -1 : fromException (/opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24) >> -2 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) >> -3 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) >> -4 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:64-78) >> -5 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:18-25) >> -6 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) >> -7 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) >> -8 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-43) >> -9 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-13) >> -10 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:252:6-25) >> -11 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:(252,3)-(253,54)) >> -12 : stableModuleNameCmp (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:62:29-78) >> -13 : compare (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:42:23-49) >> -14 : fs_sbs (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) >> -15 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:44-53) >> -16 : fs_sbs (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:207:7-12) >> -17 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:31-40) >> -18 : lexicalCompareFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:253:3-54) >> -19 : uniq (/opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10) >> -20 : moduleNameFS (/opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35) >> ... >> [] λ> :back >> Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24 >> _result :: Maybe GHC.Utils.Panic.Plain.PlainGhcException >> e :: SomeAsyncException >> [-1: /opt/exp/ghc/ghc-landing/compiler/GHC/Utils/Panic.hs:114:19-24] λ> :back >> Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10 >> _result :: Int >> uniq :: Int >> [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> uniq >> 603980920 >> [-2: /opt/exp/ghc/ghc-landing/compiler/GHC/Data/FastString.hs:205:7-10] λ> :back >> Logged breakpoint at /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35 >> _result :: ModuleName >> mod :: ModuleName >> [-3: /opt/exp/ghc/ghc-landing/compiler/GHC/Unit/Module/Name.hs:72:33-35] λ> mod >> ModuleName "GHC.Tc.Solver.Canonical" >> >> et cetera >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From nr at cs.tufts.edu Thu Oct 28 20:57:57 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Thu, 28 Oct 2021 16:57:57 -0400 Subject: 8-bit and 16-bit arithmetic Message-ID: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> On x86, GHC can translate 8-bit and 16-bit operations directly into the 8-bit and 16-bit machine instructions that the hardware supports. But there are other platforms on which the smallest unit of arithmetic may be 32 or even 64 bits. Is there a central module in GHC that can take care of rewriting 8-bit and 16-bit operations into 32-bit or 64-bit operations? Or is each back end on its own for this? (One of my students did some nice work on implementing this transformation with a minimal set of sign-extension and zero-extension operations: https://www.cs.tufts.edu/~nr/pubs/widen.pdf.) Norman From carter.schonwald at gmail.com Thu Oct 28 21:12:45 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 28 Oct 2021 17:12:45 -0400 Subject: 8-bit and 16-bit arithmetic In-Reply-To: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> References: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> Message-ID: I think thats done on a per backend basis (though theres been a lot of changes since i last looked at some of the relevent pieces). (i'm actually based in Cambridge MA for the next 1-2 years if you wanna brain storm IRL sometime) On Thu, Oct 28, 2021 at 4:59 PM Norman Ramsey wrote: > On x86, GHC can translate 8-bit and 16-bit operations directly > into the 8-bit and 16-bit machine instructions that the hardware > supports. But there are other platforms on which the smallest > unit of arithmetic may be 32 or even 64 bits. Is there a central > module in GHC that can take care of rewriting 8-bit and 16-bit operations > into 32-bit or 64-bit operations? Or is each back end on its own > for this? > > (One of my students did some nice work on implementing this transformation > with a minimal set of sign-extension and zero-extension operations: > https://www.cs.tufts.edu/~nr/pubs/widen.pdf.) > > > Norman > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Thu Oct 28 21:18:01 2021 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Thu, 28 Oct 2021 22:18:01 +0100 Subject: Exact Print Annotations : Anchor in a SrcSpan Message-ID: I have been updating the ghc-exactprint library for real world use cases on the about to be released GHC 9.2.1, and realised I need to be able to put an Anchor into every SrcSpan in the ParsedSource AST. I prepared !6854 to sort it out in master and turned to the problem of GHC 9.2.1, where I had missed the boat. And then I discovered that we have SrcSpan defined as data SrcSpan = RealSrcSpan !RealSrcSpan !(Maybe BufSpan) | UnhelpfulSpan !UnhelpfulSpanReason and the (Maybe BufSpan) is only used for attaching haddock comments after parsing. This means there is an isomorphism between the RealSrcSpan variant and an Anchor, which I take advantage of with the code in [1], by using the Maybe to encode the AnchorOperation and the BufSpan to encode the DeltaPos. And it struck me that perhaps we should make this a more official approach. The only problem is the detail of the BufSpan, to be able to play both roles cleanly. Alan [1] https://gist.github.com/alanz/5e262599ab79138606cdfcf3792ef635 -------------- next part -------------- An HTML attachment was scrubbed... URL: From klebinger.andreas at gmx.at Thu Oct 28 21:29:52 2021 From: klebinger.andreas at gmx.at (Andreas Klebinger) Date: Thu, 28 Oct 2021 23:29:52 +0200 Subject: 8-bit and 16-bit arithmetic In-Reply-To: References: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> Message-ID: <7faebd47-bf83-8821-e200-c0f61473548d@gmx.at> I think carter has it still right that it happens in the backends. If a new backend doesn't support these we could move this up into Cmm though without much issue I think. Am 28/10/2021 um 23:12 schrieb Carter Schonwald: > I think thats done on a per backend basis (though theres been a lot of > changes since i last looked at some of the relevent pieces). (i'm > actually based in Cambridge MA for the next 1-2 years if you wanna > brain storm IRL sometime) > > On Thu, Oct 28, 2021 at 4:59 PM Norman Ramsey wrote: > > On x86, GHC can translate 8-bit and 16-bit operations directly > into the 8-bit and 16-bit machine instructions that the hardware > supports.  But there are other platforms on which the smallest > unit of arithmetic may be 32 or even 64 bits.  Is there a central > module in GHC that can take care of rewriting 8-bit and 16-bit > operations > into 32-bit or 64-bit operations?  Or is each back end on its own > for this? > > (One of my students did some nice work on implementing this > transformation > with a minimal set of sign-extension and zero-extension operations: > https://www.cs.tufts.edu/~nr/pubs/widen.pdf.) > > > Norman > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at smart-cactus.org Thu Oct 28 21:37:52 2021 From: ben at smart-cactus.org (Ben Gamari) Date: Thu, 28 Oct 2021 17:37:52 -0400 Subject: 8-bit and 16-bit arithmetic In-Reply-To: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> References: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> Message-ID: <87o878u8yx.fsf@smart-cactus.org> Norman Ramsey writes: > On x86, GHC can translate 8-bit and 16-bit operations directly > into the 8-bit and 16-bit machine instructions that the hardware > supports. But there are other platforms on which the smallest > unit of arithmetic may be 32 or even 64 bits. Is there a central > module in GHC that can take care of rewriting 8-bit and 16-bit operations > into 32-bit or 64-bit operations? Or is each back end on its own > for this? > > (One of my students did some nice work on implementing this transformation > with a minimal set of sign-extension and zero-extension operations: > https://www.cs.tufts.edu/~nr/pubs/widen.pdf.) > As Carter indicated, this is currently done on a per-backend basis. This could indeed probably be consolidated, although we would want to make sure that in so doing we do not leave easy money on the table: It seems plausible to me that the backend may be able to generate better code than a naive lowering to wide arithmetic might otherwise generate. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From carter.schonwald at gmail.com Thu Oct 28 22:00:09 2021 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 28 Oct 2021 18:00:09 -0400 Subject: 8-bit and 16-bit arithmetic In-Reply-To: <87o878u8yx.fsf@smart-cactus.org> References: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> <87o878u8yx.fsf@smart-cactus.org> Message-ID: yeah, like, currently the XOR for setting registers to zero trick / code optimization (first implemented in ghc backend by reid barton) is done as part of the pretty printer on X86/AMD_64 targets this and a lot of other easy win peephole optimizations that are platform /target dependent happen in the pretty printer atm I thnk On Thu, Oct 28, 2021 at 5:38 PM Ben Gamari wrote: > Norman Ramsey writes: > > > On x86, GHC can translate 8-bit and 16-bit operations directly > > into the 8-bit and 16-bit machine instructions that the hardware > > supports. But there are other platforms on which the smallest > > unit of arithmetic may be 32 or even 64 bits. Is there a central > > module in GHC that can take care of rewriting 8-bit and 16-bit operations > > into 32-bit or 64-bit operations? Or is each back end on its own > > for this? > > > > (One of my students did some nice work on implementing this > transformation > > with a minimal set of sign-extension and zero-extension operations: > > https://www.cs.tufts.edu/~nr/pubs/widen.pdf.) > > > As Carter indicated, this is currently done on a per-backend basis. This > could indeed probably be consolidated, although we would want to make > sure that in so doing we do not leave easy money on the table: It seems > plausible to me that the backend may be able to generate better code > than a naive lowering to wide arithmetic might otherwise generate. > > Cheers, > > - Ben > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Fri Oct 29 14:43:02 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Fri, 29 Oct 2021 14:43:02 +0000 Subject: Exact Print Annotations : Anchor in a SrcSpan In-Reply-To: References: Message-ID: Alan I'm way behind with this exact-print stuff and Anchors in particular. If you and your co-workers on it are confident you know what to do, that's great - although as ever, please document the design carefully. (I volunteer as a reader of such a design overview. I know that a current draft exists.) If you want a design discussion with others less closely involved then do suggest it -- probably a synchronous meeting with a tutorial element would be helpful. thanks for working on this in such a sustained way. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simonpj at microsoft.com will cease to work. Use simon.peytonjones at gmail.com instead. (For now, it just forwards to simonpj at microsoft.com.) From: ghc-devs On Behalf Of Alan & Kim Zimmerman Sent: 28 October 2021 22:18 To: ghc-devs Subject: Exact Print Annotations : Anchor in a SrcSpan I have been updating the ghc-exactprint library for real world use cases on the about to be released GHC 9.2.1, and realised I need to be able to put an Anchor into every SrcSpan in the ParsedSource AST. I prepared !6854 to sort it out in master and turned to the problem of GHC 9.2.1, where I had missed the boat. And then I discovered that we have SrcSpan defined as data SrcSpan = RealSrcSpan !RealSrcSpan !(Maybe BufSpan) | UnhelpfulSpan !UnhelpfulSpanReason and the (Maybe BufSpan) is only used for attaching haddock comments after parsing. This means there is an isomorphism between the RealSrcSpan variant and an Anchor, which I take advantage of with the code in [1], by using the Maybe to encode the AnchorOperation and the BufSpan to encode the DeltaPos. And it struck me that perhaps we should make this a more official approach. The only problem is the detail of the BufSpan, to be able to play both roles cleanly. Alan [1] https://gist.github.com/alanz/5e262599ab79138606cdfcf3792ef635 -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Fri Oct 29 15:07:05 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Fri, 29 Oct 2021 15:07:05 +0000 Subject: Exact Print Annotations : Anchor in a SrcSpan In-Reply-To: References: Message-ID: <010f017ccc971344-4fae3e1b-43ae-4e91-90ac-07e73ba0e3c0-000000@us-east-2.amazonses.com> I don't remember the details precisely, but I do know that the BufSpan was added to allow for reliable comparisons of SrcSpans in the presence of #line pragams. I've included Vlad, who is the resident expert on this aspect of locations. My instinct is to lean against repurposing the existing slot just because it happens to fit, unless there is a semantic argument for why the Maybe BufSpan and the Anchor represent the same underlying concept. Richard > On Oct 28, 2021, at 5:18 PM, Alan & Kim Zimmerman wrote: > > I have been updating the ghc-exactprint library for real world use cases on the about to be released GHC 9.2.1, and realised I need to be able to put an Anchor into every SrcSpan in the ParsedSource AST. > > I prepared !6854 to sort it out in master and turned to the problem of GHC 9.2.1, where I had missed the boat. > > And then I discovered that we have SrcSpan defined as > > data SrcSpan = > RealSrcSpan !RealSrcSpan !(Maybe BufSpan) > | UnhelpfulSpan !UnhelpfulSpanReason > > and the (Maybe BufSpan) is only used for attaching haddock comments after parsing. > > This means there is an isomorphism between the RealSrcSpan variant and an Anchor, which I take advantage of with the code in [1], by using the Maybe to encode the AnchorOperation and the BufSpan to encode the DeltaPos. > > And it struck me that perhaps we should make this a more official approach. The only problem is the detail of the BufSpan, to be able to play both roles cleanly. > > Alan > > [1] https://gist.github.com/alanz/5e262599ab79138606cdfcf3792ef635 > > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Fri Oct 29 15:44:42 2021 From: ben at well-typed.com (Ben Gamari) Date: Fri, 29 Oct 2021 11:44:42 -0400 Subject: [ANNOUNCE] GHC 9.2.1 now available Message-ID: <87lf2bu98a.fsf@smart-cactus.org> Hi all, The GHC developers are very happy to at long last announce the availability of GHC 9.2.1. Binary distributions, source distributions, and documentation are available at https://downloads.haskell.org/ghc/9.2.1 GHC 9.2 brings a number of exciting features including: * A native code generation backend for AArch64, significantly speeding compilation time on ARM platforms like the Apple M1. * Many changes in the area of records, including the new `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well as Support for `DuplicateRecordFields` with `PatternSynonyms`. * Introduction of the new `GHC2021` language extension set, giving users convenient access to a larger set of language extensions which have been long considered stable. * Merging of `ghc-exactprint` into the GHC tree, providing infrastructure for source-to-source program rewriting out-of-the-box. * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism over levity of boxed objects (#17526) * Implementation of the `UnliftedDataTypes` extension, allowing users to define types which do not admit lazy evaluation ([proposal]) * The new [`-hi` profiling] mechanism which provides significantly improved insight into thunk leaks. * Support for the `ghc-debug` out-of-process heap inspection library [ghc-debug] * Significant improvements in the bytecode interpreter, allowing more programs to be efficently run in GHCi and Template Haskell splices. * Support for profiling of pinned objects with the cost-centre profiler (#7275) * Faster compilation and a smaller memory footprint * Introduction of Haddock documentation support in TemplateHaskell (#5467) Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous contributors whose on-going financial and in-kind support has facilitated GHC maintenance and release management over the years. Moreover, this release would not have been possible without the hundreds of open-source contributors whose work comprise this release. As always, do open a [ticket] if you see anything amiss. Happy testing, - Ben [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html [proposal]: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst [-hi profiling]: https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ [ghc-debug]: http://ghc.gitlab.haskell.org/ghc-debug/ [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 905 bytes Desc: not available URL: From alan.zimm at gmail.com Fri Oct 29 16:19:28 2021 From: alan.zimm at gmail.com (Alan & Kim Zimmerman) Date: Fri, 29 Oct 2021 17:19:28 +0100 Subject: Exact Print Annotations : Anchor in a SrcSpan In-Reply-To: References: <010f017ccc971344-4fae3e1b-43ae-4e91-90ac-07e73ba0e3c0-000000@us-east-2.amazonses.com> Message-ID: I agree on not re-using accidentally available structures. But it got me thinking that maybe the BufSpan could be something else. I’m somewhat confused by the fact that we agreed to do it post-merge, but > all further work has been in some other direction. > > My work since the merge has been on consolidating the actual use-case for the exact print annotations, which means making sure that the (still external) ghc-exactprint library is still able to support the existing use-cases. My current driver for that is porting retrie[1] to use it, which has brought up the changes that I have been doing to GHC recently. Once that is done, I plan to update the in-tree exact printing to match, and then contemplate actioning plan B. Alan [1] https://github.com/alanz/retrie/tree/ghc-9.2 -------------- next part -------------- An HTML attachment was scrubbed... URL: From nr at cs.tufts.edu Fri Oct 29 17:29:37 2021 From: nr at cs.tufts.edu (Norman Ramsey) Date: Fri, 29 Oct 2021 13:29:37 -0400 Subject: 8-bit and 16-bit arithmetic In-Reply-To: <87o878u8yx.fsf@smart-cactus.org> (sfid-H-20211028-185411-+62.37-1@multi.osbf.lua) References: <20211028205757.E78F52C2ECC@homedog.cs.tufts.edu> <87o878u8yx.fsf@smart-cactus.org> (sfid-H-20211028-185411-+62.37-1@multi.osbf.lua) Message-ID: <20211029172937.F10B72C281F@homedog.cs.tufts.edu> > Norman Ramsey writes: > > > On x86, GHC can translate 8-bit and 16-bit operations directly > > into the 8-bit and 16-bit machine instructions that the hardware > > supports. But there are other platforms on which the smallest > > unit of arithmetic may be 32 or even 64 bits. Is there a central > > module in GHC that can take care of rewriting 8-bit and 16-bit operations > > into 32-bit or 64-bit operations? Or is each back end on its own > > for this? > > > As Carter indicated, this is currently done on a per-backend basis. This > could indeed probably be consolidated, although we would want to make > sure that in so doing we do not leave easy money on the table: It seems > plausible to me that the backend may be able to generate better code > than a naive lowering to wide arithmetic might otherwise generate. The main opportunity here is the opportunity to leave garbage in the high bits of a machine register---that is, the opportunity to avoid sign extension or zero extension, which on most relevant platforms costs two instructions. The more context you have, the more likely it is that you can allow intermediate results to hold garbage. We built the context using a little type system, which would probably be easiest to apply at a high level: STG or even Core. There may also be opportunities in allowing the back end to decide how to implement "sign extend" and "zero extend," although in my experience these are less likely. (In a quick trawl through the source tree, I didn't find a definition of `PrimOp`, so I don't know whether "sign extend" and "zero extend" are already available as primitives.) Norman From george.colpitts at gmail.com Fri Oct 29 17:33:33 2021 From: george.colpitts at gmail.com (George Colpitts) Date: Fri, 29 Oct 2021 14:33:33 -0300 Subject: [ANNOUNCE] GHC 9.2.1 now available In-Reply-To: <87lf2bu98a.fsf@smart-cactus.org> References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Great news! Install works on mac os if you do xattr -rc . before doing make install The mail didn't mention that nor is it mentioned in the INSTALL file. I thought this had been fixed. I guess I'm mistaken or this is only an issue for me. Thanks again for getting this out! There's a lot of great stuff in the release. Cheers George On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: > Hi all, > > The GHC developers are very happy to at long last announce the > availability of GHC 9.2.1. Binary distributions, source distributions, > and documentation are available at > > https://downloads.haskell.org/ghc/9.2.1 > > GHC 9.2 brings a number of exciting features including: > > * A native code generation backend for AArch64, significantly speeding > compilation time on ARM platforms like the Apple M1. > > * Many changes in the area of records, including the new > `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well > as Support for `DuplicateRecordFields` with `PatternSynonyms`. > > * Introduction of the new `GHC2021` language extension set, giving > users convenient access to a larger set of language extensions which > have been long considered stable. > > * Merging of `ghc-exactprint` into the GHC tree, providing > infrastructure for source-to-source program rewriting out-of-the-box. > > * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism > over levity of boxed objects (#17526) > > * Implementation of the `UnliftedDataTypes` extension, allowing users > to define types which do not admit lazy evaluation ([proposal]) > > * The new [`-hi` profiling] mechanism which provides significantly > improved insight into thunk leaks. > > * Support for the `ghc-debug` out-of-process heap inspection library > [ghc-debug] > > * Significant improvements in the bytecode interpreter, allowing more > programs to be efficently run in GHCi and Template Haskell splices. > > * Support for profiling of pinned objects with the cost-centre profiler > (#7275) > > * Faster compilation and a smaller memory footprint > > * Introduction of Haddock documentation support in TemplateHaskell (#5467) > > Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake > pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous > contributors whose on-going financial and in-kind support has > facilitated GHC maintenance and release management over the years. > Moreover, this release would not have been possible without the hundreds > of open-source contributors whose work comprise this release. > > As always, do open a [ticket] if you see anything amiss. > > Happy testing, > > - Ben > > > [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html > [proposal]: > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst > [-hi > > profiling]: > https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ > [ghc-debug > ]: > http://ghc.gitlab.haskell.org/ghc-debug/ > [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From george.colpitts at gmail.com Sat Oct 30 15:38:54 2021 From: george.colpitts at gmail.com (George Colpitts) Date: Sat, 30 Oct 2021 12:38:54 -0300 Subject: regression in ghc / cabal integration in 9.2.1 In-Reply-To: <87lf2bu98a.fsf@smart-cactus.org> References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Thanks Ben! There seems to be a regression in ghc / cabal integration in 9.2.1. In 9.2.1 if I do cabal install vector Compilation of a file containing import Data.Vector main = undefined fails with Could not find module ‘Data.Vector’ Perhaps you meant Data.Functor (from base-4.16.0.0) Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 2 | import Data.Vector | ^^^^^^^^^^^^^^^^^^ The preceding works on ghc 9.0.1 Should I file a bug against Cabal? Thanks George On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: > Hi all, > > The GHC developers are very happy to at long last announce the > availability of GHC 9.2.1. Binary distributions, source distributions, > and documentation are available at > > https://downloads.haskell.org/ghc/9.2.1 > > GHC 9.2 brings a number of exciting features including: > > * A native code generation backend for AArch64, significantly speeding > compilation time on ARM platforms like the Apple M1. > > * Many changes in the area of records, including the new > `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well > as Support for `DuplicateRecordFields` with `PatternSynonyms`. > > * Introduction of the new `GHC2021` language extension set, giving > users convenient access to a larger set of language extensions which > have been long considered stable. > > * Merging of `ghc-exactprint` into the GHC tree, providing > infrastructure for source-to-source program rewriting out-of-the-box. > > * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism > over levity of boxed objects (#17526) > > * Implementation of the `UnliftedDataTypes` extension, allowing users > to define types which do not admit lazy evaluation ([proposal]) > > * The new [`-hi` profiling] mechanism which provides significantly > improved insight into thunk leaks. > > * Support for the `ghc-debug` out-of-process heap inspection library > [ghc-debug] > > * Significant improvements in the bytecode interpreter, allowing more > programs to be efficently run in GHCi and Template Haskell splices. > > * Support for profiling of pinned objects with the cost-centre profiler > (#7275) > > * Faster compilation and a smaller memory footprint > > * Introduction of Haddock documentation support in TemplateHaskell (#5467) > > Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake > pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous > contributors whose on-going financial and in-kind support has > facilitated GHC maintenance and release management over the years. > Moreover, this release would not have been possible without the hundreds > of open-source contributors whose work comprise this release. > > As always, do open a [ticket] if you see anything amiss. > > Happy testing, > > - Ben > > > [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html > [proposal]: > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst > [-hi > > profiling]: > https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ > [ghc-debug > ]: > http://ghc.gitlab.haskell.org/ghc-debug/ > [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mikolaj at well-typed.com Sat Oct 30 18:38:02 2021 From: mikolaj at well-typed.com (Mikolaj Konarski) Date: Sat, 30 Oct 2021 20:38:02 +0200 Subject: regression in ghc / cabal integration in 9.2.1 In-Reply-To: References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Hi George, Since many versions of cabal, `install` only installs executables, not libraries, so if that worked for you, you must have had an old version of cabal. Please see https://github.com/haskell/cabal/issues/6481 for some context and to help you find a new workflow that works for you (ideally, a standard one). Kind regards, Mikolaj On Sat, Oct 30, 2021 at 5:40 PM George Colpitts wrote: > > Thanks Ben! > > There seems to be a regression in ghc / cabal integration in 9.2.1. > > In 9.2.1 if I do > > cabal install vector > > Compilation of a file containing > > > import Data.Vector > > > main = undefined > > > fails with > > Could not find module ‘Data.Vector’ > Perhaps you meant Data.Functor (from base-4.16.0.0) > Use -v (or `:set -v` in ghci) to see a list of the files searched for. > | > 2 | import Data.Vector > | ^^^^^^^^^^^^^^^^^^ > > The preceding works on ghc 9.0.1 > > Should I file a bug against Cabal? > > Thanks > George > > On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: >> >> Hi all, >> >> The GHC developers are very happy to at long last announce the >> availability of GHC 9.2.1. Binary distributions, source distributions, >> and documentation are available at >> >> https://downloads.haskell.org/ghc/9.2.1 >> >> GHC 9.2 brings a number of exciting features including: >> >> * A native code generation backend for AArch64, significantly speeding >> compilation time on ARM platforms like the Apple M1. >> >> * Many changes in the area of records, including the new >> `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well >> as Support for `DuplicateRecordFields` with `PatternSynonyms`. >> >> * Introduction of the new `GHC2021` language extension set, giving >> users convenient access to a larger set of language extensions which >> have been long considered stable. >> >> * Merging of `ghc-exactprint` into the GHC tree, providing >> infrastructure for source-to-source program rewriting out-of-the-box. >> >> * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism >> over levity of boxed objects (#17526) >> >> * Implementation of the `UnliftedDataTypes` extension, allowing users >> to define types which do not admit lazy evaluation ([proposal]) >> >> * The new [`-hi` profiling] mechanism which provides significantly >> improved insight into thunk leaks. >> >> * Support for the `ghc-debug` out-of-process heap inspection library >> [ghc-debug] >> >> * Significant improvements in the bytecode interpreter, allowing more >> programs to be efficently run in GHCi and Template Haskell splices. >> >> * Support for profiling of pinned objects with the cost-centre profiler >> (#7275) >> >> * Faster compilation and a smaller memory footprint >> >> * Introduction of Haddock documentation support in TemplateHaskell (#5467) >> >> Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake >> pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous >> contributors whose on-going financial and in-kind support has >> facilitated GHC maintenance and release management over the years. >> Moreover, this release would not have been possible without the hundreds >> of open-source contributors whose work comprise this release. >> >> As always, do open a [ticket] if you see anything amiss. >> >> Happy testing, >> >> - Ben >> >> >> [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html >> [proposal]: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst >> [-hi profiling]: https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ >> [ghc-debug]: http://ghc.gitlab.haskell.org/ghc-debug/ >> [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new >> _______________________________________________ >> ghc-devs mailing list >> ghc-devs at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs From george.colpitts at gmail.com Sat Oct 30 19:23:26 2021 From: george.colpitts at gmail.com (George Colpitts) Date: Sat, 30 Oct 2021 16:23:26 -0300 Subject: regression in ghc / cabal integration in 9.2.1 In-Reply-To: References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Thanks for the quick response Mikolaj. Sorry for the confusion, with cabal install I did use --lib but accidentally omitted that in my original email. In 9.0.1 this results in a successful compilation but in 9.2.1 it does not thus I believe this is a regression. Here's the output I got in 9.2.1: bash-3.2$ cabal install vector --lib Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 Resolving dependencies... Up to date bash-3.2$ ghc buggc.hs [1 of 1] Compiling Main ( buggc.hs, buggc.o ) buggc.hs:2:1: error: Could not find module ‘Data.Vector’ Perhaps you meant Data.Functor (from base-4.16.0.0) Use -v (or `:set -v` in ghci) to see a list of the files searched for. | 2 | import Data.Vector However I did figure out a workaround: cabal v1-install. As far as I can tell cabal (v2-) install breaks ghc-pkg and compilation. With cabal (v2-) install the workaround for ghc-pkg is to add the option "-f $HOME/.cabal/store/ghc-9.2.1/package.db" to the end of the command "ghc-pkg list". For compilation the workaround is to add "-package-db $HOME/.cabal/store/ghc-9.2.1/package.db" to the ghc-pkg. I don't understand why it was necessary for cabal v2-install to be incompatible with cabal v1-install. Is there a link to any documentation and justification for these incompatible changes? Thanks again, George On Sat, Oct 30, 2021 at 3:38 PM Mikolaj Konarski wrote: > Hi George, > > Since many versions of cabal, `install` only installs executables, not > libraries, so if that worked for you, you must have had an old version > of cabal. > > Please see https://github.com/haskell/cabal/issues/6481 for some > context and to help you find a new workflow that works for you > (ideally, a standard one). > > Kind regards, > Mikolaj > > On Sat, Oct 30, 2021 at 5:40 PM George Colpitts > wrote: > > > > Thanks Ben! > > > > There seems to be a regression in ghc / cabal integration in 9.2.1. > > > > In 9.2.1 if I do > > > > cabal install vector > > > > Compilation of a file containing > > > > > > import Data.Vector > > > > > > main = undefined > > > > > > fails with > > > > Could not find module ‘Data.Vector’ > > Perhaps you meant Data.Functor (from base-4.16.0.0) > > Use -v (or `:set -v` in ghci) to see a list of the files searched > for. > > | > > 2 | import Data.Vector > > | ^^^^^^^^^^^^^^^^^^ > > > > The preceding works on ghc 9.0.1 > > > > Should I file a bug against Cabal? > > > > Thanks > > George > > > > On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: > >> > >> Hi all, > >> > >> The GHC developers are very happy to at long last announce the > >> availability of GHC 9.2.1. Binary distributions, source distributions, > >> and documentation are available at > >> > >> https://downloads.haskell.org/ghc/9.2.1 > >> > >> GHC 9.2 brings a number of exciting features including: > >> > >> * A native code generation backend for AArch64, significantly speeding > >> compilation time on ARM platforms like the Apple M1. > >> > >> * Many changes in the area of records, including the new > >> `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well > >> as Support for `DuplicateRecordFields` with `PatternSynonyms`. > >> > >> * Introduction of the new `GHC2021` language extension set, giving > >> users convenient access to a larger set of language extensions which > >> have been long considered stable. > >> > >> * Merging of `ghc-exactprint` into the GHC tree, providing > >> infrastructure for source-to-source program rewriting out-of-the-box. > >> > >> * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism > >> over levity of boxed objects (#17526) > >> > >> * Implementation of the `UnliftedDataTypes` extension, allowing users > >> to define types which do not admit lazy evaluation ([proposal]) > >> > >> * The new [`-hi` profiling] mechanism which provides significantly > >> improved insight into thunk leaks. > >> > >> * Support for the `ghc-debug` out-of-process heap inspection library > >> [ghc-debug] > >> > >> * Significant improvements in the bytecode interpreter, allowing more > >> programs to be efficently run in GHCi and Template Haskell splices. > >> > >> * Support for profiling of pinned objects with the cost-centre profiler > >> (#7275) > >> > >> * Faster compilation and a smaller memory footprint > >> > >> * Introduction of Haddock documentation support in TemplateHaskell > (#5467) > >> > >> Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake > >> pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous > >> contributors whose on-going financial and in-kind support has > >> facilitated GHC maintenance and release management over the years. > >> Moreover, this release would not have been possible without the hundreds > >> of open-source contributors whose work comprise this release. > >> > >> As always, do open a [ticket] if you see anything amiss. > >> > >> Happy testing, > >> > >> - Ben > >> > >> > >> [apple-m1]: > https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html > >> [proposal]: > https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst > >> [-hi profiling]: > https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ > >> [ghc-debug]: http://ghc.gitlab.haskell.org/ghc-debug/ > >> [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new > >> _______________________________________________ > >> ghc-devs mailing list > >> ghc-devs at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sat Oct 30 19:43:45 2021 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 30 Oct 2021 15:43:45 -0400 Subject: regression in ghc / cabal integration in 9.2.1 In-Reply-To: References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Wasn't there specifically a new cabal version released to deal with 9.2.1? 3.4.1.0 / 3.6.2.0? On Sat, Oct 30, 2021 at 3:24 PM George Colpitts wrote: > > Thanks for the quick response Mikolaj. Sorry for the confusion, with cabal install I did use --lib but accidentally omitted that in my original email. In 9.0.1 this results in a successful compilation but in 9.2.1 it does not thus I believe this is a regression. > > Here's the output I got in 9.2.1: > > bash-3.2$ cabal install vector --lib > Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports > 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 > Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports > 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 > Resolving dependencies... > Up to date > bash-3.2$ ghc buggc.hs > [1 of 1] Compiling Main ( buggc.hs, buggc.o ) > > > buggc.hs:2:1: error: > Could not find module ‘Data.Vector’ > Perhaps you meant Data.Functor (from base-4.16.0.0) > Use -v (or `:set -v` in ghci) to see a list of the files searched for. > | > 2 | import Data.Vector > > > However I did figure out a workaround: cabal v1-install. > > As far as I can tell cabal (v2-) install breaks ghc-pkg and compilation. With cabal (v2-) install the workaround for ghc-pkg is to add the option "-f $HOME/.cabal/store/ghc-9.2.1/package.db" to the end of the command "ghc-pkg list". For compilation the workaround is to add "-package-db $HOME/.cabal/store/ghc-9.2.1/package.db" to the ghc-pkg. I don't understand why it was necessary for cabal v2-install to be incompatible with cabal v1-install. Is there a link to any documentation and justification for these incompatible changes? > > Thanks again, > George > > > > On Sat, Oct 30, 2021 at 3:38 PM Mikolaj Konarski wrote: >> >> Hi George, >> >> Since many versions of cabal, `install` only installs executables, not >> libraries, so if that worked for you, you must have had an old version >> of cabal. >> >> Please see https://github.com/haskell/cabal/issues/6481 for some >> context and to help you find a new workflow that works for you >> (ideally, a standard one). >> >> Kind regards, >> Mikolaj >> >> On Sat, Oct 30, 2021 at 5:40 PM George Colpitts >> wrote: >> > >> > Thanks Ben! >> > >> > There seems to be a regression in ghc / cabal integration in 9.2.1. >> > >> > In 9.2.1 if I do >> > >> > cabal install vector >> > >> > Compilation of a file containing >> > >> > >> > import Data.Vector >> > >> > >> > main = undefined >> > >> > >> > fails with >> > >> > Could not find module ‘Data.Vector’ >> > Perhaps you meant Data.Functor (from base-4.16.0.0) >> > Use -v (or `:set -v` in ghci) to see a list of the files searched for. >> > | >> > 2 | import Data.Vector >> > | ^^^^^^^^^^^^^^^^^^ >> > >> > The preceding works on ghc 9.0.1 >> > >> > Should I file a bug against Cabal? >> > >> > Thanks >> > George >> > >> > On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: >> >> >> >> Hi all, >> >> >> >> The GHC developers are very happy to at long last announce the >> >> availability of GHC 9.2.1. Binary distributions, source distributions, >> >> and documentation are available at >> >> >> >> https://downloads.haskell.org/ghc/9.2.1 >> >> >> >> GHC 9.2 brings a number of exciting features including: >> >> >> >> * A native code generation backend for AArch64, significantly speeding >> >> compilation time on ARM platforms like the Apple M1. >> >> >> >> * Many changes in the area of records, including the new >> >> `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well >> >> as Support for `DuplicateRecordFields` with `PatternSynonyms`. >> >> >> >> * Introduction of the new `GHC2021` language extension set, giving >> >> users convenient access to a larger set of language extensions which >> >> have been long considered stable. >> >> >> >> * Merging of `ghc-exactprint` into the GHC tree, providing >> >> infrastructure for source-to-source program rewriting out-of-the-box. >> >> >> >> * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism >> >> over levity of boxed objects (#17526) >> >> >> >> * Implementation of the `UnliftedDataTypes` extension, allowing users >> >> to define types which do not admit lazy evaluation ([proposal]) >> >> >> >> * The new [`-hi` profiling] mechanism which provides significantly >> >> improved insight into thunk leaks. >> >> >> >> * Support for the `ghc-debug` out-of-process heap inspection library >> >> [ghc-debug] >> >> >> >> * Significant improvements in the bytecode interpreter, allowing more >> >> programs to be efficently run in GHCi and Template Haskell splices. >> >> >> >> * Support for profiling of pinned objects with the cost-centre profiler >> >> (#7275) >> >> >> >> * Faster compilation and a smaller memory footprint >> >> >> >> * Introduction of Haddock documentation support in TemplateHaskell (#5467) >> >> >> >> Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake >> >> pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous >> >> contributors whose on-going financial and in-kind support has >> >> facilitated GHC maintenance and release management over the years. >> >> Moreover, this release would not have been possible without the hundreds >> >> of open-source contributors whose work comprise this release. >> >> >> >> As always, do open a [ticket] if you see anything amiss. >> >> >> >> Happy testing, >> >> >> >> - Ben >> >> >> >> >> >> [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html >> >> [proposal]: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst >> >> [-hi profiling]: https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ >> >> [ghc-debug]: http://ghc.gitlab.haskell.org/ghc-debug/ >> >> [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new >> >> _______________________________________________ >> >> ghc-devs mailing list >> >> ghc-devs at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs >> > >> > _______________________________________________ >> > ghc-devs mailing list >> > ghc-devs at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > _______________________________________________ > ghc-devs mailing list > ghc-devs at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs -- brandon s allbery kf8nh allbery.b at gmail.com From mikolaj at well-typed.com Sat Oct 30 19:48:11 2021 From: mikolaj at well-typed.com (Mikolaj Konarski) Date: Sat, 30 Oct 2021 21:48:11 +0200 Subject: regression in ghc / cabal integration in 9.2.1 In-Reply-To: References: <87lf2bu98a.fsf@smart-cactus.org> Message-ID: Hi George, Have you looked at the ticket I gave you? Here's one linked from it mentioning the topic of ghc-pkg compatibility with v2-install: https://github.com/haskell/cabal/issues/6508 I'm afraid we don't have any systematic exposition of cabal history with rationale for its major changes, but there's a changelog and the commit log. If you'd like to contribute something better, please do. Why the difference between GHC versions, I don't know, or whether upgrading your cabal would help (I doubt it). Regarding your workflow, perhaps ask around or look up in cabal tickets how other people do this now? I never run ghc directly, so I don't know. Best, Mikolaj On Sat, Oct 30, 2021 at 9:44 PM Brandon Allbery wrote: > > Wasn't there specifically a new cabal version released to deal with > 9.2.1? 3.4.1.0 / 3.6.2.0? > > On Sat, Oct 30, 2021 at 3:24 PM George Colpitts > wrote: > > > > Thanks for the quick response Mikolaj. Sorry for the confusion, with cabal install I did use --lib but accidentally omitted that in my original email. In 9.0.1 this results in a successful compilation but in 9.2.1 it does not thus I believe this is a regression. > > > > Here's the output I got in 9.2.1: > > > > bash-3.2$ cabal install vector --lib > > Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports > > 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 > > Warning: Unknown/unsupported 'ghc' version detected (Cabal 3.4.0.0 supports > > 'ghc' version < 9.1): /usr/local/bin/ghc is version 9.2.1 > > Resolving dependencies... > > Up to date > > bash-3.2$ ghc buggc.hs > > [1 of 1] Compiling Main ( buggc.hs, buggc.o ) > > > > > > buggc.hs:2:1: error: > > Could not find module ‘Data.Vector’ > > Perhaps you meant Data.Functor (from base-4.16.0.0) > > Use -v (or `:set -v` in ghci) to see a list of the files searched for. > > | > > 2 | import Data.Vector > > > > > > However I did figure out a workaround: cabal v1-install. > > > > As far as I can tell cabal (v2-) install breaks ghc-pkg and compilation. With cabal (v2-) install the workaround for ghc-pkg is to add the option "-f $HOME/.cabal/store/ghc-9.2.1/package.db" to the end of the command "ghc-pkg list". For compilation the workaround is to add "-package-db $HOME/.cabal/store/ghc-9.2.1/package.db" to the ghc-pkg. I don't understand why it was necessary for cabal v2-install to be incompatible with cabal v1-install. Is there a link to any documentation and justification for these incompatible changes? > > > > Thanks again, > > George > > > > > > > > On Sat, Oct 30, 2021 at 3:38 PM Mikolaj Konarski wrote: > >> > >> Hi George, > >> > >> Since many versions of cabal, `install` only installs executables, not > >> libraries, so if that worked for you, you must have had an old version > >> of cabal. > >> > >> Please see https://github.com/haskell/cabal/issues/6481 for some > >> context and to help you find a new workflow that works for you > >> (ideally, a standard one). > >> > >> Kind regards, > >> Mikolaj > >> > >> On Sat, Oct 30, 2021 at 5:40 PM George Colpitts > >> wrote: > >> > > >> > Thanks Ben! > >> > > >> > There seems to be a regression in ghc / cabal integration in 9.2.1. > >> > > >> > In 9.2.1 if I do > >> > > >> > cabal install vector > >> > > >> > Compilation of a file containing > >> > > >> > > >> > import Data.Vector > >> > > >> > > >> > main = undefined > >> > > >> > > >> > fails with > >> > > >> > Could not find module ‘Data.Vector’ > >> > Perhaps you meant Data.Functor (from base-4.16.0.0) > >> > Use -v (or `:set -v` in ghci) to see a list of the files searched for. > >> > | > >> > 2 | import Data.Vector > >> > | ^^^^^^^^^^^^^^^^^^ > >> > > >> > The preceding works on ghc 9.0.1 > >> > > >> > Should I file a bug against Cabal? > >> > > >> > Thanks > >> > George > >> > > >> > On Fri, Oct 29, 2021 at 12:54 PM Ben Gamari wrote: > >> >> > >> >> Hi all, > >> >> > >> >> The GHC developers are very happy to at long last announce the > >> >> availability of GHC 9.2.1. Binary distributions, source distributions, > >> >> and documentation are available at > >> >> > >> >> https://downloads.haskell.org/ghc/9.2.1 > >> >> > >> >> GHC 9.2 brings a number of exciting features including: > >> >> > >> >> * A native code generation backend for AArch64, significantly speeding > >> >> compilation time on ARM platforms like the Apple M1. > >> >> > >> >> * Many changes in the area of records, including the new > >> >> `RecordDotSyntax` and `NoFieldSelectors` language extensions, as well > >> >> as Support for `DuplicateRecordFields` with `PatternSynonyms`. > >> >> > >> >> * Introduction of the new `GHC2021` language extension set, giving > >> >> users convenient access to a larger set of language extensions which > >> >> have been long considered stable. > >> >> > >> >> * Merging of `ghc-exactprint` into the GHC tree, providing > >> >> infrastructure for source-to-source program rewriting out-of-the-box. > >> >> > >> >> * Introduction of a `BoxedRep` `RuntimeRep`, allowing for polymorphism > >> >> over levity of boxed objects (#17526) > >> >> > >> >> * Implementation of the `UnliftedDataTypes` extension, allowing users > >> >> to define types which do not admit lazy evaluation ([proposal]) > >> >> > >> >> * The new [`-hi` profiling] mechanism which provides significantly > >> >> improved insight into thunk leaks. > >> >> > >> >> * Support for the `ghc-debug` out-of-process heap inspection library > >> >> [ghc-debug] > >> >> > >> >> * Significant improvements in the bytecode interpreter, allowing more > >> >> programs to be efficently run in GHCi and Template Haskell splices. > >> >> > >> >> * Support for profiling of pinned objects with the cost-centre profiler > >> >> (#7275) > >> >> > >> >> * Faster compilation and a smaller memory footprint > >> >> > >> >> * Introduction of Haddock documentation support in TemplateHaskell (#5467) > >> >> > >> >> Finally, thank you to Microsoft Research, GitHub, IOHK, the Zw3rk stake > >> >> pool, Tweag I/O, Serokell, Equinix, SimSpace, and other anonymous > >> >> contributors whose on-going financial and in-kind support has > >> >> facilitated GHC maintenance and release management over the years. > >> >> Moreover, this release would not have been possible without the hundreds > >> >> of open-source contributors whose work comprise this release. > >> >> > >> >> As always, do open a [ticket] if you see anything amiss. > >> >> > >> >> Happy testing, > >> >> > >> >> - Ben > >> >> > >> >> > >> >> [apple-m1]: https://www.haskell.org/ghc/blog/20210309-apple-m1-story.html > >> >> [proposal]: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst > >> >> [-hi profiling]: https://well-typed.com/blog/2021/01/first-look-at-hi-profiling-mode/ > >> >> [ghc-debug]: http://ghc.gitlab.haskell.org/ghc-debug/ > >> >> [ticket]: https://gitlab.haskell.org/ghc/ghc/-/issues/new > >> >> _______________________________________________ > >> >> ghc-devs mailing list > >> >> ghc-devs at haskell.org > >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > >> > > >> > _______________________________________________ > >> > ghc-devs mailing list > >> > ghc-devs at haskell.org > >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > _______________________________________________ > > ghc-devs mailing list > > ghc-devs at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs > > > > -- > brandon s allbery kf8nh > allbery.b at gmail.com