StgRhsClosure freevar and argument name duplicates

Hi, Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates? Cheers, Csaba data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

Is it possible that GHC generates STG with invalid binding semantics for
certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github
master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for
duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers, Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
From: ghc-devs

An example for the duplication please check the divModInteger
https://github.com/ghc/ghc/blob/master/libraries/integer-simple/GHC/Integer/...
function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger **:: Integer -> Integer
-> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim
using GHC.Tuple
using GHC.Types
GHC.Integer.Type.divModInteger {-083-} =
closure (F:) (B:
n.s84123 {-s84123-}
d.s84124 {-s84124-}) {
case GHC.Integer.Type.quotRemInteger {-084-}
n.s84123 {-s84123-}
d.s84124 {-s84124-}
of qr.s84125 {-s84125-} {
GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ->
let $j.s84128 {-s84128-} =
closure (F:
d.s84124 {-s84124-}
* ipv.s84126 {-s84126-}*
* ipv1.s84127 {-s84127-}*
* ipv.s84126 {-s84126-}*
*ipv1.s84127 {-s84127-}*) (B:
wild.s84129 {-s84129-}) {
let $j1.s84130 {-s84130-} =
closure (F:
d.s84124 {-s84124-}
ipv.s84126 {-s84126-}
ipv1.s84127 {-s84127-}
ipv.s84126 {-s84126-}
ipv1.s84127 {-s84127-}
wild.s84129 {-s84129-}) (B:
wild1.s84131 {-s84131-}) {
case _stg_prim_negateInt#
wild.s84129 {-s84129-}
of sat.s84132 {-s84132-} {
DEFAULT ->
case _stg_prim_==#
wild1.s84131 {-s84131-}
sat.s84132 {-s84132-}
of sat.s84133 {-s84133-} {
DEFAULT ->
case _stg_prim_tagToEnum#
sat.s84133 {-s84133-}
of wild2.s84134 {-s84134-} {
GHC.Types.False {-612-} ->
GHC.Prim.(#,#) {-86-}
ipv.s84126 {-s84126-}
ipv1.s84127 {-s84127-}
GHC.Types.True {-645-} ->
case GHC.Integer.Type.plusInteger {-066-}
ipv1.s84127 {-s84127-}
d.s84124 {-s84124-}
of r'.s84135 {-s84135-} {
DEFAULT ->
case GHC.Integer.Type.plusInteger {-066-}
ipv.s84126 {-s84126-}
GHC.Integer.Type.lvl11 {-r50574-}
of q'.s84136 {-s84136-} {
DEFAULT ->
GHC.Prim.(#,#) {-86-}
q'.s84136 {-s84136-}
r'.s84135 {-s84135-}
}
}
}
}
}}
in case ipv1.s84127 {-s84127-}
of wild1.s84137 {-s84137-} {
GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} ->
case _stg_prim_<#
i#.s84138 {-s84138-} 0#
of sat.s84140 {-s84140-} {
DEFAULT ->
case _stg_prim_>#
i#.s84138 {-s84138-} 0#
of sat.s84139 {-s84139-} {
DEFAULT ->
case _stg_prim_-#
sat.s84139 {-s84139-}
sat.s84140 {-s84140-}
of sat.s84141 {-s84141-} {
DEFAULT ->
$j1.s84130 {-s84130-}
sat.s84141 {-s84141-}
}
}
}
GHC.Integer.Type.Jp# {-r5813-} dt.s84142 {-s84142-} ->
$j1.s84130 {-s84130-} 1#
GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} ->
$j1.s84130 {-s84130-} -1#
}}
in case d.s84124 {-s84124-}
of wild.s84144 {-s84144-} {
GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} ->
case _stg_prim_<#
i#.s84145 {-s84145-} 0#
of sat.s84147 {-s84147-} {
DEFAULT ->
case _stg_prim_>#
i#.s84145 {-s84145-} 0#
of sat.s84146 {-s84146-} {
DEFAULT ->
case _stg_prim_-#
sat.s84146 {-s84146-}
sat.s84147 {-s84147-}
of sat.s84148 {-s84148-} {
DEFAULT ->
$j.s84128 {-s84128-}
sat.s84148 {-s84148-}
}
}
}
GHC.Integer.Type.Jp# {-r5813-} dt.s84149 {-s84149-} ->
$j.s84128 {-s84128-} 1#
GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} ->
$j.s84128 {-s84128-} -1#
}
}}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer...
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
An example for the duplication please check the divModInteger https://github.com/ghc/ghc/blob/master/libraries/integer-simple/GHC/Integer/... function from integer-simple GHC.Integer.Type. The STG (GHC 8.2.2) generated from *divModInteger **:: Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like: module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
From: Csaba Hruska

My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure
- top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to
the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones
Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7C0a8467d53f9145e88f9208d6433c6e0e%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770324161848413&sdata=SQrzwfSloPvCTaEAUd4M3PVHanfjX37xjdRE6BXn2Pc%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7C0a8467d53f9145e88f9208d6433c6e0e%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770324161858421&sdata=Tqq7MeFA91LqKwitneuRxoDVwO8EAhWBY%2FN5RmdA4Bg%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C0a8467d53f9145e88f9208d6433c6e0e%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770324161868430&sdata=ajvn3QOaaWDYGqqTKtPe4fYTJaNHGVGmFsfuKN1Psyo%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C0a8467d53f9145e88f9208d6433c6e0e%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770324161868430&sdata=ajvn3QOaaWDYGqqTKtPe4fYTJaNHGVGmFsfuKN1Psyo%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
From: Csaba Hruska

I've also noticed that there are two Main.main top-level binders in the
generated STG with different uniques?
And GHC produces a working executable.
Is Main.main an exception or does top-level names have some kind of "should
be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones
I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones
wrote: Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594092291&sdata=re0I7r77Hli0UuEv07vBNRRrWttdDLGE8BaYYQZNr8o%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=sEVZfZHmc9%2BQxzp8bQijgiRBPvGv5U0lsQi9lElUoj8%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=KaYvZjgoFE%2BNT%2FbQ4mZlKqB8Q%2FT50CUstmJS3RGtur0%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594112198&sdata=baugV3HdRfINk51GmbD51LtoW1A3S7p4yKXvIXseEgA%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

Correction: I've also noticed that there are two Main.main top-level
binders in the generated STG with different uniques.
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques? And GHC produces a working executable. Is Main.main an exception or does top-level names have some kind of "should be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones
wrote: I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones
wrote: Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594092291&sdata=re0I7r77Hli0UuEv07vBNRRrWttdDLGE8BaYYQZNr8o%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=sEVZfZHmc9%2BQxzp8bQijgiRBPvGv5U0lsQi9lElUoj8%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=KaYvZjgoFE%2BNT%2FbQ4mZlKqB8Q%2FT50CUstmJS3RGtur0%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594112198&sdata=baugV3HdRfINk51GmbD51LtoW1A3S7p4yKXvIXseEgA%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

You can reproduce the error with the GHC HEAD and with the attached patch
for StgLinter.
The patch adds scope checking for the linter.
I've also attached the linter's error output against GHC HEAD.
Compile GHC HEAD with the following settings:
GhcStage1HcOpts=
GhcStage2HcOpts=-O2 -haddock -dstg-lint
GhcStage3HcOpts=-O2 -haddock -dstg-lint
Regards,
Csaba
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
Correction: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques.
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques? And GHC produces a working executable. Is Main.main an exception or does top-level names have some kind of "should be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones
wrote: I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones < simonpj@microsoft.com> wrote:
Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594092291&sdata=re0I7r77Hli0UuEv07vBNRRrWttdDLGE8BaYYQZNr8o%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=sEVZfZHmc9%2BQxzp8bQijgiRBPvGv5U0lsQi9lElUoj8%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594102189&sdata=KaYvZjgoFE%2BNT%2FbQ4mZlKqB8Q%2FT50CUstmJS3RGtur0%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7Cd47aada6162e4c2da86608d643d720dd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636770988594112198&sdata=baugV3HdRfINk51GmbD51LtoW1A3S7p4yKXvIXseEgA%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

can you open a Trac ticket, and explain how to reproduce it? Does it require a patch, or does -ddump-stg show it?
thanks
Simion
From: Csaba Hruska

Ok, I'll open a ticket.
To reproduce:
1. patch GHC head: *git apply StgScopeCheck.patch*
2. make sure every compiled stg is linted: *add -dstg-lint* to
GhcStage2HcOpts
GhcLibHcOpts GhcRtsHcOpts config vars
3. compile GHC HEAD
On Tue, Nov 6, 2018 at 4:39 PM Simon Peyton Jones
can you open a Trac ticket, and explain how to reproduce it? Does it require a patch, or does -ddump-stg show it?
thanks
Simion
*From:* Csaba Hruska
*Sent:* 06 November 2018 15:36 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates You can reproduce the error with the GHC HEAD and with the attached patch for StgLinter.
The patch adds scope checking for the linter.
I've also attached the linter's error output against GHC HEAD.
Compile GHC HEAD with the following settings:
GhcStage1HcOpts= GhcStage2HcOpts=-O2 -haddock -dstg-lint GhcStage3HcOpts=-O2 -haddock -dstg-lint
Regards,
Csaba
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: Correction: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques.
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques?
And GHC produces a working executable.
Is Main.main an exception or does top-level names have some kind of "should be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones
wrote: I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones
wrote: Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034475485&sdata=tglY4lglir%2FKqm3ApXo9gW4gHCWeRIBjP7UMEytNjxQ%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034485494&sdata=6u7J6besY3OM9zfcr0x0LRuo7zJRphr6iHOq6xwO7mo%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

https://ghc.haskell.org/trac/ghc/ticket/15867
On Tue, Nov 6, 2018 at 4:47 PM Csaba Hruska
Ok, I'll open a ticket. To reproduce:
1. patch GHC head: *git apply StgScopeCheck.patch* 2. make sure every compiled stg is linted: *add -dstg-lint* to GhcStage2HcOpts GhcLibHcOpts GhcRtsHcOpts config vars 3. compile GHC HEAD
On Tue, Nov 6, 2018 at 4:39 PM Simon Peyton Jones
wrote: can you open a Trac ticket, and explain how to reproduce it? Does it require a patch, or does -ddump-stg show it?
thanks
Simion
*From:* Csaba Hruska
*Sent:* 06 November 2018 15:36 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates You can reproduce the error with the GHC HEAD and with the attached patch for StgLinter.
The patch adds scope checking for the linter.
I've also attached the linter's error output against GHC HEAD.
Compile GHC HEAD with the following settings:
GhcStage1HcOpts= GhcStage2HcOpts=-O2 -haddock -dstg-lint GhcStage3HcOpts=-O2 -haddock -dstg-lint
Regards,
Csaba
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: Correction: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques.
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques?
And GHC produces a working executable.
Is Main.main an exception or does top-level names have some kind of "should be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones
wrote: I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones
wrote: Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034475485&sdata=tglY4lglir%2FKqm3ApXo9gW4gHCWeRIBjP7UMEytNjxQ%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034485494&sdata=6u7J6besY3OM9zfcr0x0LRuo7zJRphr6iHOq6xwO7mo%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

I have a question.
Do unique names have SSA semantic in STG?
Can multiple (StgRec/StgNonRec) binding id have the same unique value?
On Tue, Nov 6, 2018 at 5:10 PM Csaba Hruska
https://ghc.haskell.org/trac/ghc/ticket/15867
On Tue, Nov 6, 2018 at 4:47 PM Csaba Hruska
wrote: Ok, I'll open a ticket. To reproduce:
1. patch GHC head: *git apply StgScopeCheck.patch* 2. make sure every compiled stg is linted: *add -dstg-lint* to GhcStage2HcOpts GhcLibHcOpts GhcRtsHcOpts config vars 3. compile GHC HEAD
On Tue, Nov 6, 2018 at 4:39 PM Simon Peyton Jones
wrote: can you open a Trac ticket, and explain how to reproduce it? Does it require a patch, or does -ddump-stg show it?
thanks
Simion
*From:* Csaba Hruska
*Sent:* 06 November 2018 15:36 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates You can reproduce the error with the GHC HEAD and with the attached patch for StgLinter.
The patch adds scope checking for the linter.
I've also attached the linter's error output against GHC HEAD.
Compile GHC HEAD with the following settings:
GhcStage1HcOpts= GhcStage2HcOpts=-O2 -haddock -dstg-lint GhcStage3HcOpts=-O2 -haddock -dstg-lint
Regards,
Csaba
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: Correction: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques.
On Tue, Nov 6, 2018 at 12:19 PM Csaba Hruska
wrote: I've also noticed that there are two Main.main top-level binders in the generated STG with different uniques?
And GHC produces a working executable.
Is Main.main an exception or does top-level names have some kind of "should be exported" property?
On Tue, Nov 6, 2018 at 12:02 PM Simon Peyton Jones < simonpj@microsoft.com> wrote:
I think top level names should be unique in occ-names; because those occ-names generate the symbols in the binary.
Simon
*From:* Csaba Hruska
*Sent:* 06 November 2018 11:01 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates My plan is to extend GHC's STG linter to check the following properties:
- uniqueness of free var and arg list of StgRhsClosure - top level binding name uniqueness
I'll patch my local GHC 8.2.2 and GHC HEAD. I'll also attach the patch to the ticket.
I have a question regarding top level names.
Should the top-level names be unique as occ names or just in unique values?
If not, then what is the rule?
Thanks,
Csaba
On Tue, Nov 6, 2018 at 11:13 AM Simon Peyton Jones < simonpj@microsoft.com> wrote:
Does this happen in HEAD with GHC’s own STG printer? If so, could you file a Trac ticket – it’s clearly wrong.
But I do wonder if it could perhaps be something to do with your branch?
Thanks
Simon
*From:* Csaba Hruska
*Sent:* 05 November 2018 16:33 *To:* Simon Peyton Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Correction!
The problem happens in integer-gmp:
https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer... https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-gmp%2Fsrc%2FGHC%2FInteger%2FType.hs%23L761-L770&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034475485&sdata=tglY4lglir%2FKqm3ApXo9gW4gHCWeRIBjP7UMEytNjxQ%3D&reserved=0
On Mon, Nov 5, 2018 at 5:27 PM Csaba Hruska
wrote: An example for the duplication please check the divModInteger https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc%2Fghc%2Fblob%2Fmaster%2Flibraries%2Finteger-simple%2FGHC%2FInteger%2FType.hs%23L373-L380&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034485494&sdata=6u7J6besY3OM9zfcr0x0LRuo7zJRphr6iHOq6xwO7mo%3D&reserved=0 function from integer-simple GHC.Integer.Type.
The STG (GHC 8.2.2) generated from *divModInteger* *::** Integer -> Integer -> (# Integer, Integer #) *contains duplications in a closure binder list.
Using my custom STG printer it looks like:
module GHC.Integer.Type where
using GHC.Prim using GHC.Tuple using GHC.Types
GHC.Integer.Type.divModInteger {-083-} = closure (F:) (B: n.s84123 {-s84123-} d.s84124 {-s84124-}) { case GHC.Integer.Type.quotRemInteger {-084-} n.s84123 {-s84123-} d.s84124 {-s84124-} of qr.s84125 {-s84125-} { GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} -> let $j.s84128 {-s84128-} = closure (F: d.s84124 {-s84124-} * ipv.s84126 {-s84126-}* * ipv1.s84127 {-s84127-}* * ipv.s84126 {-s84126-}* *ipv1.s84127 {-s84127-}*) (B: wild.s84129 {-s84129-}) { let $j1.s84130 {-s84130-} = closure (F: d.s84124 {-s84124-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} wild.s84129 {-s84129-}) (B: wild1.s84131 {-s84131-}) { case _stg_prim_negateInt# wild.s84129 {-s84129-} of sat.s84132 {-s84132-} { DEFAULT -> case _stg_prim_==# wild1.s84131 {-s84131-} sat.s84132 {-s84132-} of sat.s84133 {-s84133-} { DEFAULT -> case _stg_prim_tagToEnum# sat.s84133 {-s84133-} of wild2.s84134 {-s84134-} { GHC.Types.False {-612-} -> GHC.Prim.(#,#) {-86-} ipv.s84126 {-s84126-} ipv1.s84127 {-s84127-} GHC.Types.True {-645-} -> case GHC.Integer.Type.plusInteger {-066-} ipv1.s84127 {-s84127-} d.s84124 {-s84124-} of r'.s84135 {-s84135-} { DEFAULT -> case GHC.Integer.Type.plusInteger {-066-} ipv.s84126 {-s84126-} GHC.Integer.Type.lvl11 {-r50574-} of q'.s84136 {-s84136-} { DEFAULT -> GHC.Prim.(#,#) {-86-} q'.s84136 {-s84136-} r'.s84135 {-s84135-} } } } } }}
in case ipv1.s84127 {-s84127-} of wild1.s84137 {-s84137-} { GHC.Integer.Type.S# {-621-} i#.s84138 {-s84138-} -> case _stg_prim_<# i#.s84138 {-s84138-} 0# of sat.s84140 {-s84140-} { DEFAULT -> case _stg_prim_># i#.s84138 {-s84138-} 0# of sat.s84139 {-s84139-} { DEFAULT -> case _stg_prim_-# sat.s84139 {-s84139-} sat.s84140 {-s84140-} of sat.s84141 {-s84141-} { DEFAULT -> $j1.s84130 {-s84130-} sat.s84141 {-s84141-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84142 {-s84142-} -> $j1.s84130 {-s84130-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84143 {-s84143-} -> $j1.s84130 {-s84130-} -1# }}
in case d.s84124 {-s84124-} of wild.s84144 {-s84144-} { GHC.Integer.Type.S# {-621-} i#.s84145 {-s84145-} -> case _stg_prim_<# i#.s84145 {-s84145-} 0# of sat.s84147 {-s84147-} { DEFAULT -> case _stg_prim_># i#.s84145 {-s84145-} 0# of sat.s84146 {-s84146-} { DEFAULT -> case _stg_prim_-# sat.s84146 {-s84146-} sat.s84147 {-s84147-} of sat.s84148 {-s84148-} { DEFAULT -> $j.s84128 {-s84128-} sat.s84148 {-s84148-} } } } GHC.Integer.Type.Jp# https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2FGHC.Integer.Type.Jp%23&data=02%7C01%7Csimonpj%40microsoft.com%7C8ed5614402be4321be6908d643fda441%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636771154034495502&sdata=2WLaJGm7NgH0FvibSDarfwBraI9nn0uAZVUH6CwaMno%3D&reserved=0 {-r5813-} dt.s84149 {-s84149-} -> $j.s84128 {-s84128-} 1# GHC.Integer.Type.Jn# {-r5814-} dt.s84150 {-s84150-} -> $j.s84128 {-s84128-} -1# } }}
On Mon, Nov 5, 2018 at 2:08 PM Simon Peyton Jones
wrote: I don’t think there should be duplicates in either. Do you have a test case that shows duplicates?
Simon
*From:* ghc-devs
*On Behalf Of *Csaba Hruska *Sent:* 04 November 2018 11:22 *To:* ghc-devs@haskell.org *Subject:* Re: StgRhsClosure freevar and argument name duplicates Is it possible that GHC generates STG with invalid binding semantics for certain cases that the Cmm codegen fix or ignore?
This could explain my observations.
I've checked the Stg linter source (StgLint.hs ; GHC 8.2.2 and github master) and it does not check StgRhsClosure free var and binder list at all.
And the scope checker function (addInScopeVars) does not check for duplicates.
Any thoughts?
Cheers,
Csaba
On Sat, Nov 3, 2018 at 9:53 AM Csaba Hruska
wrote: Hi,
Can StgRhsClosure's freevar list ([occ]) or argument list ([bndr]) contain duplicates?
Cheers,
Csaba
data GenStgRhs bndr occ = StgRhsClosure CostCentreStack -- CCS to be attached (default is CurrentCCS) StgBinderInfo -- Info about how this binder is used (see below) *[occ]* -- non-global free vars; a list, rather than -- a set, because order is important !UpdateFlag -- ReEntrant | Updatable | SingleEntry *[bndr]* -- arguments; if empty, then not a function; -- as above, order is important. (GenStgExpr bndr occ) -- body

Do unique names have SSA semantic in STG?
I’m not sure what you mean. STG just obeys normal lexical scoping.
Can multiple (StgRec/StgNonRec) binding id have the same unique value?
No: the uniques are used during code generation to general labels that should be globally unique. At least I think this is so.
Simon
From: Csaba Hruska
participants (2)
-
Csaba Hruska
-
Simon Peyton Jones