Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings

Hi, I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!). I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not. The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode? Thanks, Gergo

So if I understand correctly, OtherCon is only created here:
https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf759...
simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs rhs)
= assert (null bndrs) $
do { let env' = addBinderUnfolding env case_bndr'
(mkOtherCon imposs_deflt_cons)
-- Record the constructors that the case-binder *can't* be.
; rhs' <- simplExprC env' rhs cont'
; return (Alt DEFAULT [] rhs') }
What you should know is that in Core case-expressions are actually more
like:
case scrut as b of alts
where `b` binds the evaluated result of `scrut.
So if I am to understand the `simplAlt` code correctly, `case_bndr'` is the
binder for the evaluated result of `scrut`.
And what is recorded in the unfolding is that once we get to the DEFAULT
pattern, we know that `case_bndr'` cannot be the constructors in
`imposs_deflt_cons` (probably the constructor matched by the other
alternatives).
Now... there's also a FloutOut pass, which might have floated that
`case_bndr'` to the TopLevel.
And I think that is what you're seeing, and I think you can simply ignore
them.
Also... another thing that you should know is that -fexpose-all-unfoldings
doesn't actually expose *all* unfoldings.
Bottoming bindings are never exposed.
That's why in the Clash compiler we have the following code when loading
core-expressions from .hi files
https://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc8...
loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe
CoreSyn.CoreExpr
loadExprFromTyThing bndr tyThing = case tyThing of
GHC.AnId _id | Var.isId _id ->
let _idInfo = Var.idInfo _id
unfolding = IdInfo.unfoldingInfo _idInfo
in case unfolding of
CoreSyn.CoreUnfolding {} ->
Just (CoreSyn.unfoldingTemplate unfolding)
CoreSyn.DFunUnfolding dfbndrs dc es ->
Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es))
CoreSyn.NoUnfolding
#if MIN_VERSION_ghc(9,0,0)
| Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo
#else
| Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo
#endif
-> do
let noUnfoldingErr = "no_unfolding " ++ showPpr
unsafeGlobalDynFlags bndr
Just (MkCore.mkAbsentErrorApp (Var.varType _id) noUnfoldingErr)
_ -> Nothing
_ -> Nothing
i.e. when we encounter a NoUnfolding with a bottoming demand signature, we
conjure an absentError out of thin air.
On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő
Hi,
I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo
-- You received this message because you are subscribed to the Google Groups "Clash - Hardware Description Language" group. To unsubscribe from this group and stop receiving emails from it, send an email to clash-language+unsubscribe@googlegroups.com. To view this discussion on the web visit https://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011... .

This doesn't quite match my experience. For example, the following toplevel definition gets an `OtherCon []` unfolding: nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x:ys) : r as can be seen with: $ ghc -fforce-recomp -fexpose-all-unfoldings -ddump-prep -dsuppress-uniques A.hs -- RHS size: {terms: 37, types: 55, coercions: 0, joins: 0/6} A.nonEmptySubsequences [Occ=LoopBreaker] :: forall a. [a] -> [[a]] [GblId, Arity=1, Unf=OtherCon []] A.nonEmptySubsequences = \ (@ a) (ds [Occ=Once1!] :: [a]) -> ... So this is not a lifted `case`-bound variable, but a bonafide user-originating toplevel definition. And its value also isn't bottom. On Fri, 1 Apr 2022, Christiaan Baaij wrote:
So if I understand correctly, OtherCon is only created here:https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf759... mpiler/GHC/Core/Opt/Simplify.hs#L3071-3077
simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs rhs) = assert (null bndrs) $ do { let env' = addBinderUnfolding env case_bndr' (mkOtherCon imposs_deflt_cons) -- Record the constructors that the case-binder *can't* be. ; rhs' <- simplExprC env' rhs cont' ; return (Alt DEFAULT [] rhs') }
What you should know is that in Core case-expressions are actually more like:
case scrut as b of alts
where `b` binds the evaluated result of `scrut.
So if I am to understand the `simplAlt` code correctly, `case_bndr'` is the binder for the evaluated result of `scrut`. And what is recorded in the unfolding is that once we get to the DEFAULT pattern, we know that `case_bndr'` cannot be the constructors in `imposs_deflt_cons` (probably the constructor matched by the other alternatives).
Now... there's also a FloutOut pass, which might have floated that `case_bndr'` to the TopLevel. And I think that is what you're seeing, and I think you can simply ignore them.
Also... another thing that you should know is that -fexpose-all-unfoldings doesn't actually expose *all* unfoldings. Bottoming bindings are never exposed. That's why in the Clash compiler we have the following code when loading core-expressions from .hi fileshttps://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc8... 61f3f/clash-ghc/src-ghc/Clash/GHC/LoadInterfaceFiles.hs#L473-L481
loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe CoreSyn.CoreExpr loadExprFromTyThing bndr tyThing = case tyThing of GHC.AnId _id | Var.isId _id -> let _idInfo = Var.idInfo _id unfolding = IdInfo.unfoldingInfo _idInfo in case unfolding of CoreSyn.CoreUnfolding {} -> Just (CoreSyn.unfoldingTemplate unfolding) CoreSyn.DFunUnfolding dfbndrs dc es -> Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es)) CoreSyn.NoUnfolding #if MIN_VERSION_ghc(9,0,0) | Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo #else | Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo #endif -> do let noUnfoldingErr = "no_unfolding " ++ showPpr unsafeGlobalDynFlags bndr Just (MkCore.mkAbsentErrorApp (Var.varType _id) noUnfoldingErr) _ -> Nothing _ -> Nothing
i.e. when we encounter a NoUnfolding with a bottoming demand signature, we conjure an absentError out of thin air.
On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő
wrote: Hi, I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo
-- You received this message because you are subscribed to the Google Groups "Clash - Hardware Description Language" group. To unsubscribe from this group and stop receiving emails from it, send an email to clash-language+unsubscribe@googlegroups.com. To view this discussion on the web visithttps://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011... 83073%40galaxy.
-- .--= ULLA! =-----------------. \ http://gergo.erdi.hu \ `---= gergo@erdi.hu =-------'

The unfolding is present if you add `-fno-omit-interface-pragmas` and dump with `-ddump-simpl`. CorePrep drops unfoldings, see Note [Drop unfoldings and rules] in GHC.CoreToStg.Prep. The logic for unfolding exposition by Tidy is now in: https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf759... If you use the GHC API you can now invoke Tidy with different TidyOpts. On 01/04/2022 15:37, ÉRDI Gergő wrote:
This doesn't quite match my experience. For example, the following toplevel definition gets an `OtherCon []` unfolding:
nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences [] = [] nonEmptySubsequences (x:xs) = [x] : foldr f [] (nonEmptySubsequences xs) where f ys r = ys : (x:ys) : r
as can be seen with:
$ ghc -fforce-recomp -fexpose-all-unfoldings -ddump-prep -dsuppress-uniques A.hs
-- RHS size: {terms: 37, types: 55, coercions: 0, joins: 0/6} A.nonEmptySubsequences [Occ=LoopBreaker] :: forall a. [a] -> [[a]] [GblId, Arity=1, Unf=OtherCon []] A.nonEmptySubsequences = \ (@ a) (ds [Occ=Once1!] :: [a]) -> ...
So this is not a lifted `case`-bound variable, but a bonafide user-originating toplevel definition. And its value also isn't bottom.
On Fri, 1 Apr 2022, Christiaan Baaij wrote:
So if I understand correctly, OtherCon is only created here:https://gitlab.haskell.org/ghc/ghc/-/blob/a952dd80d40bf6b67194a44ff71d7bf759... mpiler/GHC/Core/Opt/Simplify.hs#L3071-3077
simplAlt env _ imposs_deflt_cons case_bndr' cont' (Alt DEFAULT bndrs rhs) = assert (null bndrs) $ do { let env' = addBinderUnfolding env case_bndr' (mkOtherCon imposs_deflt_cons) -- Record the constructors that the case-binder *can't* be. ; rhs' <- simplExprC env' rhs cont' ; return (Alt DEFAULT [] rhs') }
What you should know is that in Core case-expressions are actually more like:
case scrut as b of alts
where `b` binds the evaluated result of `scrut.
So if I am to understand the `simplAlt` code correctly, `case_bndr'` is the binder for the evaluated result of `scrut`. And what is recorded in the unfolding is that once we get to the DEFAULT pattern, we know that `case_bndr'` cannot be the constructors in `imposs_deflt_cons` (probably the constructor matched by the other alternatives).
Now... there's also a FloutOut pass, which might have floated that `case_bndr'` to the TopLevel. And I think that is what you're seeing, and I think you can simply ignore them.
Also... another thing that you should know is that -fexpose-all-unfoldings doesn't actually expose *all* unfoldings. Bottoming bindings are never exposed. That's why in the Clash compiler we have the following code when loading core-expressions from .hi fileshttps://github.com/clash-lang/clash-compiler/blob/cb93b418865e244da50e1d2bc8... 61f3f/clash-ghc/src-ghc/Clash/GHC/LoadInterfaceFiles.hs#L473-L481
loadExprFromTyThing :: CoreSyn.CoreBndr -> GHC.TyThing -> Maybe CoreSyn.CoreExpr loadExprFromTyThing bndr tyThing = case tyThing of GHC.AnId _id | Var.isId _id -> let _idInfo = Var.idInfo _id unfolding = IdInfo.unfoldingInfo _idInfo in case unfolding of CoreSyn.CoreUnfolding {} -> Just (CoreSyn.unfoldingTemplate unfolding) CoreSyn.DFunUnfolding dfbndrs dc es -> Just (MkCore.mkCoreLams dfbndrs (MkCore.mkCoreConApps dc es)) CoreSyn.NoUnfolding #if MIN_VERSION_ghc(9,0,0) | Demand.isDeadEndSig $ IdInfo.strictnessInfo _idInfo #else | Demand.isBottomingSig $ IdInfo.strictnessInfo _idInfo #endif -> do let noUnfoldingErr = "no_unfolding " ++ showPpr unsafeGlobalDynFlags bndr Just (MkCore.mkAbsentErrorApp (Var.varType _id) noUnfoldingErr) _ -> Nothing _ -> Nothing
i.e. when we encounter a NoUnfolding with a bottoming demand signature, we conjure an absentError out of thin air.
On Fri, 1 Apr 2022 at 10:05, ÉRDI Gergő
wrote: Hi, I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo
-- You received this message because you are subscribed to the Google Groups "Clash - Hardware Description Language" group. To unsubscribe from this group and stop receiving emails from it, send an email to clash-language+unsubscribe@googlegroups.com. To view this discussion on the web visithttps://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011... 83073%40galaxy.
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Fri, 1 Apr 2022, Sylvain Henry wrote:
The unfolding is present if you add `-fno-omit-interface-pragmas` and dump with `-ddump-simpl`. CorePrep drops unfoldings, see Note [Drop unfoldings and rules] in GHC.CoreToStg.Prep.
Thanks, I forgot to mention that I am already using `NoOmitInterfacePragmas`, but I wasn't aware that the Prep stage drops unfoldings (and in fact, I am using Prep output in my real program). But if that's the case, how come most of my Ids still have unfoldings, and only a couple of them are missing?

I don't think any top-level Ids should have OtherCon [] unfoldings? If
they do, can you give a repro case? OtherCon [] unfoldings usually mean "I
know this variable is evaluated, but I don't know what its value is. E.g
data T = MkT !a !a
f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
You may want stronger invariants on the output of CorePrep than we have
hitherto sought. Can you explain what they are? And why you want the
output of CorePrep not CoreTidy?
Thanks
Simon
On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő
Hi,
I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I'm using Prep's output (mostly so that it's in ANF) in my full
compilation pipeline, so ideally I would save Prep'd Core in my
.hi-equivalents so that I don't have to rerun Prep on them every time
I use them.
I'll get back to you with some concrete examples of `OtherCon []` vs.
meaningful unfoldings next week.
Merging with my other question about shadowing problems with
`toIface*`, in summary it seems that what I really should be doing, is
compiling up to Tidy, taking the `CoreBinding`s from there and using
`toIfaceBinding` on them to save the definitions.
On Sat, Apr 2, 2022 at 12:53 AM Simon Peyton Jones
I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g data T = MkT !a !a f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
You may want stronger invariants on the output of CorePrep than we have hitherto sought. Can you explain what they are? And why you want the output of CorePrep not CoreTidy?
Thanks
Simon
On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő
wrote: Hi,
I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large, this works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of them are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is that it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo _______________________________________________ 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

Merging with my other question about shadowing problems with
`toIface*`, in summary it seems that what I really should be doing, is
compiling up to Tidy, taking the `CoreBinding`s from there and using
`toIfaceBinding` on them to save the definitions.
It's hard for me to be helpful here, because I don't know what invariants
you want. They might be:
- ANF
- Fully saturated primops
- No shadowing of OccNames
- Globally unique Uniques
or some combination of these. (Perhaps more -- read Note [CorePrep
Overview]!)
If you can write down precisely what you want, you can probably achieve it,
starting from either the output of Tidy or the output of Prep.
What is missing in GHC is a clear statement of the invariants on the output
of Tidy, for which I opened #21333. If you felt able to offer an MR for
that, it'd be fantastic.
Simon
On Sat, 2 Apr 2022 at 04:30, Gergő Érdi
I'm using Prep's output (mostly so that it's in ANF) in my full compilation pipeline, so ideally I would save Prep'd Core in my .hi-equivalents so that I don't have to rerun Prep on them every time I use them.
I'll get back to you with some concrete examples of `OtherCon []` vs. meaningful unfoldings next week.
Merging with my other question about shadowing problems with `toIface*`, in summary it seems that what I really should be doing, is compiling up to Tidy, taking the `CoreBinding`s from there and using `toIfaceBinding` on them to save the definitions.
On Sat, Apr 2, 2022 at 12:53 AM Simon Peyton Jones
wrote: I don't think any top-level Ids should have OtherCon [] unfoldings? If
data T = MkT !a !a f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
You may want stronger invariants on the output of CorePrep than we have hitherto sought. Can you explain what they are? And why you want the output of CorePrep not CoreTidy?
Thanks
Simon
On Fri, 1 Apr 2022 at 09:13, ÉRDI Gergő
wrote: Hi,
I'm CC-ing the Clash mailing list because I believe they should have encountered the same problem (and perhaps have found a solution to it already!).
I'm trying to use `.hi` files compiled with `ExposeAllUnfoldings` set to reconstruct full Core bindings for further processing. By and large,
works, but I get tripped up on identifiers whose unfolding is only given as `OtherCon []`. It is unclear to me what is causing this -- some of
are recursive bindings while others are not.
The problem, of course, is that if all I know about an identifier is
they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g this them that
it is `OtherCon []`, that doesn't allow me to restore its definition. So is there a way to tell GHC to put "full" unfoldings everywhere in `ExposeAllUnfoldings` mode?
Thanks, Gergo _______________________________________________ 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

Simon Peyton Jones
I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g data T = MkT !a !a f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
Is there a reason why we wouldn't potentially give a static data constructor application an OtherCon [] unfolding? I would guess that usually these are small enough to have a CoreUnfolding, but in cases where the expression is too large to have an unstable unfolding we might rather want to give it an OtherCon []. Cheers, - Ben

Top-level data structures tend to get OtherCon [] unfoldings when they
are marked NOINLINE.
KindRep bindings are one particular example, and they appear quite
often, too.
Why are KindReps are NOINLINE? Because (from Note [Grand plan for
Typeable])
The KindReps can unfortunately get quite large. Moreover, the
simplifier will
float out various pieces of them, resulting in numerous top-level
bindings.
Consequently we mark the KindRep bindings as noinline, ensuring that
the
float-outs don't make it into the interface file. This is important
since
there is generally little benefit to inlining KindReps and they would
otherwise strongly affect compiler performance.
But perhaps it's not top-level *data structures* without unfoldings that
Gergő worries about.
Sebastian
------ Originalnachricht ------
Von: "Ben Gamari"
Simon Peyton Jones
writes: I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g data T = MkT !a !a f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
Is there a reason why we wouldn't potentially give a static data constructor application an OtherCon [] unfolding? I would guess that usually these are small enough to have a CoreUnfolding, but in cases where the expression is too large to have an unstable unfolding we might rather want to give it an OtherCon [].
Cheers,
- Ben

Core Tidy also turns CoreUnfoldings to `OtherCon []` while zapping unfoldings. On 22/04/05 14:12, Sebastian Graf wrote:
Top-level data structures tend to get OtherCon [] unfoldings when they are marked NOINLINE.
KindRep bindings are one particular example, and they appear quite often, too.
Why are KindReps are NOINLINE? Because (from Note [Grand plan for Typeable])
The KindReps can unfortunately get quite large. Moreover, the simplifier will float out various pieces of them, resulting in numerous top-level bindings. Consequently we mark the KindRep bindings as noinline, ensuring that the float-outs don't make it into the interface file. This is important since there is generally little benefit to inlining KindReps and they would otherwise strongly affect compiler performance.
But perhaps it's not top-level *data structures* without unfoldings that Gergő worries about.
Sebastian
------ Originalnachricht ------ Von: "Ben Gamari"
An: "Simon Peyton Jones" ; "ÉRDI Gergő" Cc: "GHC Devs" ; clash-language@googlegroups.com Gesendet: 05.04.2022 15:53:02 Betreff: Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings Simon Peyton Jones
writes: I don't think any top-level Ids should have OtherCon [] unfoldings? If they do, can you give a repro case? OtherCon [] unfoldings usually mean "I know this variable is evaluated, but I don't know what its value is. E.g data T = MkT !a !a f (MkT x y) = ...
here x and y have OtherCon [] unfoldings. They are definitely not bottom!
Is there a reason why we wouldn't potentially give a static data constructor application an OtherCon [] unfolding? I would guess that usually these are small enough to have a CoreUnfolding, but in cases where the expression is too large to have an unstable unfolding we might rather want to give it an OtherCon [].
Cheers,
- Ben
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
participants (8)
-
Ben Gamari
-
Christiaan Baaij
-
Gergő Érdi
-
Sebastian Graf
-
Simon Peyton Jones
-
Sylvain Henry
-
Zubin Duggal
-
ÉRDI Gergő