Re: convention around pattern synonyms

2021-12-30 Thread Viktor Dukhovni
On Thu, Dec 30, 2021 at 04:46:29PM +, Richard Eisenberg wrote:

> I agree that this kind of backward-compatibility pattern synonym is
> good and shouldn't be prefixed with PS_.
> 
> But do you have a concrete example of this leakage of an internal GHC
> type via TH? While I can imagine this happening, I don't know of any
> examples in practice. Note that even enumeration types (like Role)
> have separate TH counterparts.

Perhaps my assumption that TH types directly mirror the internal AST is
not correct...  A recent user-visible change is in `ConP`

https://github.com/nikita-volkov/contravariant-extras/pull/9

-- 
Viktor.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: convention around pattern synonyms

2021-12-30 Thread Richard Eisenberg
I agree that this kind of backward-compatibility pattern synonym is good and 
shouldn't be prefixed with PS_.

But do you have a concrete example of this leakage of an internal GHC type via 
TH? While I can imagine this happening, I don't know of any examples in 
practice. Note that even enumeration types (like Role) have separate TH 
counterparts.

Richard

> On Dec 29, 2021, at 6:12 PM, Viktor Dukhovni  wrote:
> 
> Some "GHC-internal" types leak to users via TH, and their constructors
> occasionally pick up new fields, causing breakage downstream.  The extra
> field often has a sensible default (Nothing, [], ...) and it should be
> best practice to rename the constructor when adding the new field, while
> replacing the original constructor with a pattern synonym with the "old"
> signature.
> 
>   data Foo = ...
>| NewImprovedMkFoo X Y Z -- was MkFoo Y Z
> 
>   pattern MkFoo :: Foo
>   pattern MkFoo Y Z = NewImprovedMkFoo Nothing Y Z
> 
> When pattern synonyms are used to maintain a backwards-compatible API,
> there should of course be no special signalling to differentiate them
> from "real" constructors.
> 
> The boundary between "GHC-internal" and external may not always be
> obvious, some care is required to reduce leaking breakage via TH.
> 
> -- 
>   Viktor.
> ___
> 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


Re: Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
PUBLIC

Ah, at least I've figured out why exactly the simplifier does this (regardless 
of floating out due to full laziness or not): it is because the definition of 
the default implementation of (>>) is inlined. I have (>>) defined as such:

ma >> mb = ma >>= \_ -> mb

So when the simplifier encounters a call site "foo >> bar", it needs to bind 
"foo" and "bar" to avoid duplication (since "ma" and "mb" could occur multiple 
times on the right-hand side of (>>)'s definition). 

This means that the best I can hope for would be to avoid floating out "ma" and 
"mb", but the variable bindings themselves are unavoidable in the face of 
inlining (and of course I do want inlining). So I'll need to rethink my 
approach anyway.

-Original Message-
From: Erdi, Gergo 
Sent: Thursday, December 30, 2021 12:56 PM
To: Matthew Pickering 
Cc: Joachim Breitner ; ghc-devs@haskell.org
Subject: RE: [External] Re: Avoiding full laziness xform / floating-out (Re: 
What's the benefit of taking "do" blocks apart? Is there a way to turn that 
off?)

PUBLIC

Turning on various Opt_D_dump flags, I can see that this tranformation happens 
in the first iteration of the simplifier. Looking at GHC.Core.Opt.getCoreToDo, 
I would guess this corresponds to this line:

-- initial simplify: mk specialiser happy: minimum effort please
runWhen do_presimplify simpl_gently,

If I wrote my own optimisation pass, I'm not sure what it could do to inhibit 
GHC from doing this transformation later on in its pipeline. And I don't want 
to give up on the simplifier pipeline completely, since there are parts of it 
that I very much need. One of them is, unfortunately, the specializer itself -- 
and that comment in getCoreToDo makes me worried that if I somehow managed to 
get rid of this transformation (or if I skipped the simplifier pipeline 
completely and just ran the specializer out-of-band), I would break 
specialization anyway...



-Original Message-
From: Matthew Pickering  
Sent: Thursday, December 30, 2021 10:42 AM
To: Erdi, Gergo 
Cc: Joachim Breitner ; ghc-devs@haskell.org
Subject: [External] Re: Avoiding full laziness xform / floating-out (Re: What's 
the benefit of taking "do" blocks apart? Is there a way to turn that off?)


Hi Gergo,

Sounds like you might be better off writing your own optimisation pass rather 
than relying on making GHC do what you want.

Cheers

Matt

On Thu, Dec 30, 2021 at 9:05 AM Erdi, Gergo via ghc-devs  
wrote:
>
> PUBLIC
>
> Hi Joachim,
>
> Thanks for the hints!
>
> > Hi Gergo,
> >
> > Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via 
> > ghc-
> > devs:
> > > PUBLIC
> >
> > phew
>
> Yeah obviously I'm sitting here not only adding these tags, but also 
> coming up with the automated systems and also the company policies 
> forcing the usage of said systems ;)
>
> > didn't investigate deeper (maybe if you provide a small example I would), 
> > but just from looking at this:
>
> Unfortunately, it's hard to make a small example because this all 
> lives in bizarro world where "IO" isn't IO, "String" isn't [Char] etc, 
> so I can't just take the input program and pass it to vanilla GHC.
>
> >
> >  * It is generally preferable to turn local lambda expressions
> >into top-level functions. This way, instead of dynamically
> >allocating a FUN heap object, it's just a static function.
> >
> >  * sat_sKv is an IO expression? Then it is actually a function in a way
> >(taking the "State token" as an argument). So the above applies.
>
> This is "IO" but not GHC's IO, just another type with an opaque 
> definition and a Monad instance. There's no reason for GHC to think 
> that sat_sKv would be a function.
>
> Of course, sat_sKw is necessarily a function since it is the second 
> argument to bind. But only now I am noticing that even sat_sKw's 
> definition includes *yet another* floated-out variable:
>
> sat_sKv = some complicated expression 1 sat_sKu = some complicated 
> expression 2 sat_sKw = \_ -> sat_sKu main = bindIO sat_sKv sat_sKw
>
> Here, I don't see why GHC should think that sat_sKv and sat_sKu are 
> functions. For example, here's the definition of sat_sKu:
>
> sat_sKu :: IO ()
> [LclId]
> sat_sKu
>   = let {
>   sat_sRy [Occ=Once1] :: String
>   [LclId]
>   sat_sRy
> = let {
> sat_sRx [Occ=Once1] :: String
> [LclId]
> sat_sRx = unpackCStringUtf8# "\n"# } in
>   let {
> sat_sRw [Occ=Once1] :: String
> [LclId]
> sat_sRw
>   = case foobar True of {
>   False -> unpackCStringUtf8# "False"#;
>   True -> unpackCStringUtf8# "True"#
> } } in
>   sApp# sat_sRw sat_sRx } in
> putStrOut sat_sRy
>
> Here, putStrOut is so opaque that it doesn't even have a definition, 
> it is merely a name registered into GHC's name tables. So I really 
> don't see why this looks "function-y" to GHC.
>
> 

RE: [External] Re: Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
PUBLIC

Turning on various Opt_D_dump flags, I can see that this tranformation happens 
in the first iteration of the simplifier. Looking at GHC.Core.Opt.getCoreToDo, 
I would guess this corresponds to this line:

-- initial simplify: mk specialiser happy: minimum effort please
runWhen do_presimplify simpl_gently,

If I wrote my own optimisation pass, I'm not sure what it could do to inhibit 
GHC from doing this transformation later on in its pipeline. And I don't want 
to give up on the simplifier pipeline completely, since there are parts of it 
that I very much need. One of them is, unfortunately, the specializer itself -- 
and that comment in getCoreToDo makes me worried that if I somehow managed to 
get rid of this transformation (or if I skipped the simplifier pipeline 
completely and just ran the specializer out-of-band), I would break 
specialization anyway...



-Original Message-
From: Matthew Pickering  
Sent: Thursday, December 30, 2021 10:42 AM
To: Erdi, Gergo 
Cc: Joachim Breitner ; ghc-devs@haskell.org
Subject: [External] Re: Avoiding full laziness xform / floating-out (Re: What's 
the benefit of taking "do" blocks apart? Is there a way to turn that off?)


Hi Gergo,

Sounds like you might be better off writing your own optimisation pass rather 
than relying on making GHC do what you want.

Cheers

Matt

On Thu, Dec 30, 2021 at 9:05 AM Erdi, Gergo via ghc-devs  
wrote:
>
> PUBLIC
>
> Hi Joachim,
>
> Thanks for the hints!
>
> > Hi Gergo,
> >
> > Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via 
> > ghc-
> > devs:
> > > PUBLIC
> >
> > phew
>
> Yeah obviously I'm sitting here not only adding these tags, but also 
> coming up with the automated systems and also the company policies 
> forcing the usage of said systems ;)
>
> > didn't investigate deeper (maybe if you provide a small example I would), 
> > but just from looking at this:
>
> Unfortunately, it's hard to make a small example because this all 
> lives in bizarro world where "IO" isn't IO, "String" isn't [Char] etc, 
> so I can't just take the input program and pass it to vanilla GHC.
>
> >
> >  * It is generally preferable to turn local lambda expressions
> >into top-level functions. This way, instead of dynamically
> >allocating a FUN heap object, it's just a static function.
> >
> >  * sat_sKv is an IO expression? Then it is actually a function in a way
> >(taking the "State token" as an argument). So the above applies.
>
> This is "IO" but not GHC's IO, just another type with an opaque 
> definition and a Monad instance. There's no reason for GHC to think 
> that sat_sKv would be a function.
>
> Of course, sat_sKw is necessarily a function since it is the second 
> argument to bind. But only now I am noticing that even sat_sKw's 
> definition includes *yet another* floated-out variable:
>
> sat_sKv = some complicated expression 1 sat_sKu = some complicated 
> expression 2 sat_sKw = \_ -> sat_sKu main = bindIO sat_sKv sat_sKw
>
> Here, I don't see why GHC should think that sat_sKv and sat_sKu are 
> functions. For example, here's the definition of sat_sKu:
>
> sat_sKu :: IO ()
> [LclId]
> sat_sKu
>   = let {
>   sat_sRy [Occ=Once1] :: String
>   [LclId]
>   sat_sRy
> = let {
> sat_sRx [Occ=Once1] :: String
> [LclId]
> sat_sRx = unpackCStringUtf8# "\n"# } in
>   let {
> sat_sRw [Occ=Once1] :: String
> [LclId]
> sat_sRw
>   = case foobar True of {
>   False -> unpackCStringUtf8# "False"#;
>   True -> unpackCStringUtf8# "True"#
> } } in
>   sApp# sat_sRw sat_sRx } in
> putStrOut sat_sRy
>
> Here, putStrOut is so opaque that it doesn't even have a definition, 
> it is merely a name registered into GHC's name tables. So I really 
> don't see why this looks "function-y" to GHC.
>
> The reason this is all a problem for me is because I would like to 
> then interpret all these let-bindings, including the toplevel ones, as 
> eagerly defined variables. But then there is of course a difference 
> between
>
> main =
>   let a1 = someIOAction1
>   a2 = someOtherIOAction2
>   a2' = \_ -> a2
>   in bindIO a1 a2'
>
> and
>
> main =
>   let a1 = someIOAction1
>   a2 = \_ -> someIOAction2
>   in bindIO a1 a2
>
> because if the *definition* of "a2" throws (not its action), then the 
> first version will throw immediately whereas the second will only 
> throw when "main" is *run*, after running "a1".
>
> >  * I think this is the FloatOut pass. You can turn it out using
> >-fno-full-laziness. Not sure if some others passes might
> >do similar things, though.
>
> I tried turning off Opt_FullLaziness, but unfortunately I am still 
> getting the same result. I was also hopeful when I saw there's an 
> Opt_FloatIn flag, but alas that doesn't change this behaviour either 
> (and it's turned on by default anyway...)

Re: Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Matthew Pickering
Hi Gergo,

Sounds like you might be better off writing your own optimisation pass
rather than relying on making GHC do what you want.

Cheers

Matt

On Thu, Dec 30, 2021 at 9:05 AM Erdi, Gergo via ghc-devs
 wrote:
>
> PUBLIC
>
> Hi Joachim,
>
> Thanks for the hints!
>
> > Hi Gergo,
> >
> > Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via ghc-
> > devs:
> > > PUBLIC
> >
> > phew
>
> Yeah obviously I'm sitting here not only adding these tags, but also
> coming up with the automated systems and also the company policies
> forcing the usage of said systems ;)
>
> > didn't investigate deeper (maybe if you provide a small example I would), 
> > but just from looking at this:
>
> Unfortunately, it's hard to make a small example because this all
> lives in bizarro world where "IO" isn't IO, "String" isn't [Char] etc,
> so I can't just take the input program and pass it to vanilla GHC.
>
> >
> >  * It is generally preferable to turn local lambda expressions
> >into top-level functions. This way, instead of dynamically
> >allocating a FUN heap object, it's just a static function.
> >
> >  * sat_sKv is an IO expression? Then it is actually a function in a way
> >(taking the "State token" as an argument). So the above applies.
>
> This is "IO" but not GHC's IO, just another type with an opaque
> definition and a Monad instance. There's no reason for GHC to think
> that sat_sKv would be a function.
>
> Of course, sat_sKw is necessarily a function since it is the second
> argument to bind. But only now I am noticing that even sat_sKw's
> definition includes *yet another* floated-out variable:
>
> sat_sKv = some complicated expression 1
> sat_sKu = some complicated expression 2
> sat_sKw = \_ -> sat_sKu
> main = bindIO sat_sKv sat_sKw
>
> Here, I don't see why GHC should think that sat_sKv and sat_sKu are
> functions. For example, here's the definition of sat_sKu:
>
> sat_sKu :: IO ()
> [LclId]
> sat_sKu
>   = let {
>   sat_sRy [Occ=Once1] :: String
>   [LclId]
>   sat_sRy
> = let {
> sat_sRx [Occ=Once1] :: String
> [LclId]
> sat_sRx = unpackCStringUtf8# "\n"# } in
>   let {
> sat_sRw [Occ=Once1] :: String
> [LclId]
> sat_sRw
>   = case foobar True of {
>   False -> unpackCStringUtf8# "False"#;
>   True -> unpackCStringUtf8# "True"#
> } } in
>   sApp# sat_sRw sat_sRx } in
> putStrOut sat_sRy
>
> Here, putStrOut is so opaque that it doesn't even have a definition,
> it is merely a name registered into GHC's name tables. So I really
> don't see why this looks "function-y" to GHC.
>
> The reason this is all a problem for me is because I would like to
> then interpret all these let-bindings, including the toplevel ones, as
> eagerly defined variables. But then there is of course a difference between
>
> main =
>   let a1 = someIOAction1
>   a2 = someOtherIOAction2
>   a2' = \_ -> a2
>   in bindIO a1 a2'
>
> and
>
> main =
>   let a1 = someIOAction1
>   a2 = \_ -> someIOAction2
>   in bindIO a1 a2
>
> because if the *definition* of "a2" throws (not its action), then the
> first version will throw immediately whereas the second will only
> throw when "main" is *run*, after running "a1".
>
> >  * I think this is the FloatOut pass. You can turn it out using
> >-fno-full-laziness. Not sure if some others passes might
> >do similar things, though.
>
> I tried turning off Opt_FullLaziness, but unfortunately I am still
> getting the same result. I was also hopeful when I saw there's an
> Opt_FloatIn flag, but alas that doesn't change this behaviour either
> (and it's turned on by default anyway...)
>
> I'll try to make a self-contained minimal example next week.
>
> Thanks,
> Gergo
>
> -Original Message-
> From: ghc-devs  On Behalf Of Joachim Breitner
> Sent: Wednesday, December 29, 2021 8:39 PM
> To: ghc-devs@haskell.org
> Subject: [External] Re: What's the benefit of taking "do" blocks apart? Is 
> there a way to turn that off?
>
> [You don't often get email from m...@joachim-breitner.de. Learn why this is 
> important at http://aka.ms/LearnAboutSenderIdentification.]
>
> 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.
>
>
> Hi Gergo,
>
> Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via ghc-
> devs:
> > PUBLIC
>
> phew
>
> > I’m seeing ‘do’ blocks getting taking apart into top-level
> > definitions, so e.g.
> >
> > main = do
> >   some complicated expression 1
> >   some complicated expression 2
> >
> > is compiled into
> >
> > sat_sKv = some complicated expression 1 sat_sKw = \_ -> some
> > complicated expression 2 main = bindIO sat_sKv sat_sKw
> >
> > This seems to 

Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
PUBLIC

Hi Joachim,

Thanks for the hints!

> Hi Gergo,
> 
> Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via ghc-
> devs:
> > PUBLIC
> 
> phew

Yeah obviously I'm sitting here not only adding these tags, but also
coming up with the automated systems and also the company policies
forcing the usage of said systems ;)

> didn't investigate deeper (maybe if you provide a small example I would), but 
> just from looking at this:

Unfortunately, it's hard to make a small example because this all
lives in bizarro world where "IO" isn't IO, "String" isn't [Char] etc,
so I can't just take the input program and pass it to vanilla GHC.

> 
>  * It is generally preferable to turn local lambda expressions
>into top-level functions. This way, instead of dynamically
>allocating a FUN heap object, it's just a static function.
> 
>  * sat_sKv is an IO expression? Then it is actually a function in a way
>(taking the "State token" as an argument). So the above applies.

This is "IO" but not GHC's IO, just another type with an opaque
definition and a Monad instance. There's no reason for GHC to think
that sat_sKv would be a function.

Of course, sat_sKw is necessarily a function since it is the second
argument to bind. But only now I am noticing that even sat_sKw's
definition includes *yet another* floated-out variable:

sat_sKv = some complicated expression 1
sat_sKu = some complicated expression 2
sat_sKw = \_ -> sat_sKu
main = bindIO sat_sKv sat_sKw

Here, I don't see why GHC should think that sat_sKv and sat_sKu are
functions. For example, here's the definition of sat_sKu:

sat_sKu :: IO ()
[LclId]
sat_sKu
  = let {
  sat_sRy [Occ=Once1] :: String
  [LclId]
  sat_sRy
= let {
sat_sRx [Occ=Once1] :: String
[LclId]
sat_sRx = unpackCStringUtf8# "\n"# } in
  let {
sat_sRw [Occ=Once1] :: String
[LclId]
sat_sRw
  = case foobar True of {
  False -> unpackCStringUtf8# "False"#;
  True -> unpackCStringUtf8# "True"#
} } in
  sApp# sat_sRw sat_sRx } in
putStrOut sat_sRy

Here, putStrOut is so opaque that it doesn't even have a definition,
it is merely a name registered into GHC's name tables. So I really
don't see why this looks "function-y" to GHC.

The reason this is all a problem for me is because I would like to
then interpret all these let-bindings, including the toplevel ones, as
eagerly defined variables. But then there is of course a difference between

main =
  let a1 = someIOAction1
  a2 = someOtherIOAction2
  a2' = \_ -> a2
  in bindIO a1 a2'

and

main =
  let a1 = someIOAction1
  a2 = \_ -> someIOAction2
  in bindIO a1 a2

because if the *definition* of "a2" throws (not its action), then the
first version will throw immediately whereas the second will only
throw when "main" is *run*, after running "a1".

>  * I think this is the FloatOut pass. You can turn it out using
>-fno-full-laziness. Not sure if some others passes might
>do similar things, though.

I tried turning off Opt_FullLaziness, but unfortunately I am still
getting the same result. I was also hopeful when I saw there's an
Opt_FloatIn flag, but alas that doesn't change this behaviour either
(and it's turned on by default anyway...)

I'll try to make a self-contained minimal example next week.

Thanks,
Gergo

-Original Message-
From: ghc-devs  On Behalf Of Joachim Breitner
Sent: Wednesday, December 29, 2021 8:39 PM
To: ghc-devs@haskell.org
Subject: [External] Re: What's the benefit of taking "do" blocks apart? Is 
there a way to turn that off?

[You don't often get email from m...@joachim-breitner.de. Learn why this is 
important at http://aka.ms/LearnAboutSenderIdentification.]

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.


Hi Gergo,

Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via ghc-
devs:
> PUBLIC

phew

> I’m seeing ‘do’ blocks getting taking apart into top-level 
> definitions, so e.g.
>
> main = do
>   some complicated expression 1
>   some complicated expression 2
>
> is compiled into
>
> sat_sKv = some complicated expression 1 sat_sKw = \_ -> some 
> complicated expression 2 main = bindIO sat_sKv sat_sKw
>
> This seems to happen regardless of any common subexpressions, i.e. it 
> is not the case that sat_sKv or sat_sKw are used anywhere else.
>
> What is the intended benefit of this floating-out? Is there a 
> particular Core-to-Core pass that causes this? Is it possible to turn 
> it off?


didn’t investigate deeper (maybe if you provide a small example I would), but 
just from looking at this:

 * It is generally preferable to turn local lambda expressions
   into top-level functions.