RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-11 Thread Erdi, Gergo via ghc-devs
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 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo mailto:gergo.e...@sc.com>>
Sent: 11 October 2021 03:58
To: Simon Peyton Jones mailto:simo...@microsoft.com>>; 
Matthew Pickering 
mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
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 {

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-11 Thread Simon Peyton Jones via ghc-devs
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 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@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 mailto:simo...@microsoft.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; GHC 
mailto:ghc-devs@haskell.org>>
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 mailto:simo...@microsoft.com>>
Sent: Wednesday, October 6, 2021 6:12 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; GHC 
mailto:ghc-devs@haskell.org>>
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 simo...@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 

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-10 Thread Erdi, Gergo via ghc-devs
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 mailto:simo...@microsoft.com>>
Sent: Wednesday, October 6, 2021 6:12 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; GHC 
mailto:ghc-devs@haskell.org>>
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 simo...@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 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@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, 

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Erdi, Gergo via ghc-devs
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 simo...@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 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@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.___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Simon Peyton Jones via ghc-devs
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 simo...@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 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@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)
   

Re: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Erdi, Gergo via ghc-devs
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.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Matthew Pickering
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]

Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-05 Thread Erdi, Gergo via ghc-devs
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