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 <ghc-devs@haskell.org> 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=<S(LSL),U(A,U,A)>] > > (>>=) > > = \ (@(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=<S(LSL),U(A,U,A)>] > > (>>=) > > = \ (@(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 <simo...@microsoft.com> > Sent: Monday, October 4, 2021 7:29 PM > To: Erdi, Gergo <gergo.e...@sc.com> > Cc: Montelatici, Raphael Laurent <raphael.montelat...@sc.com>; GHC > <ghc-devs@haskell.org> > 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 > simo...@microsoft.com will cease to work. Use simon.peytonjo...@gmail.com > instead. (For now, it just forwards to simo...@microsoft.com.) > > > > From: ghc-devs <ghc-devs-boun...@haskell.org> On Behalf Of Erdi, Gergo via > ghc-devs > Sent: 04 October 2021 10:30 > To: 'GHC' <ghc-devs@haskell.org> > Cc: Montelatici, Raphael Laurent <raphael.montelat...@sc.com> > 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@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs