[clash-language] Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings

Sylvain Henry sylvain at haskus.fr
Fri Apr 1 13:56:05 UTC 2022


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/a952dd80d40bf6b67194a44ff71d7bf75957d29e/compiler/GHC/Driver/Config/Tidy.hs#L40

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/a952dd80d40bf6b67194a44ff71d7bf75957d29e/co
>> 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/cb93b418865e244da50e1d2bc85fbc01bf7
>> 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ő <gergo at erdi.hu> 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 at googlegroups.com.
>>       To view this discussion on the web 
>> visithttps://groups.google.com/d/msgid/clash-language/alpine.DEB.2.22.394.2204011556570.31
>>       83073%40galaxy.
>>
>>
>>
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


More information about the ghc-devs mailing list