GHC API user: How to stop simplifier from turning recursive let-bindings into mutually recursive functions

Hello GHC Devs, First some context: I'm using the GHC API to convert Haskell to digital circuit descriptions (clash compiler). When viewed as a structural description of a circuit, recursive let-bindings can be turned into feedback loops. In general, when viewed as a structural description of a circuit, recursive functions describe infinite hierarchy, i.e. they are not realisable as circuit. So now my problem: the simplifier turns recursive let-bindings to recursive functions; i.e. it is turning something which I can translate to a circuit to something which I cannot translate to a circuit. Next follows a reduced test case which exemplifies this behaviour: ``` import Control.Applicative topEntity :: [((),())] topEntity = (,) <$> outport1 <*> outport2 where (outport1, outResp1) = gpio (decodeReq 1 req) (outport2, outResp2) = gpio (decodeReq 2 req) ramResp = ram (decodeReq 0 req) req = core $ (<|>) <$> ramResp <*> ((<|>) <$> outResp1 <*> outResp2) {-# INLINE req #-} core :: [Maybe ()] -> [()] core = fmap (maybe () id) {-# NOINLINE core #-} ram :: [()] -> [Maybe ()] ram = fmap pure {-# NOINLINE ram #-} decodeReq :: Integer -> [()] -> [()] decodeReq 0 = fmap (const ()) decodeReq 1 = id decodeReq _ = fmap id {-# NOINLINE decodeReq #-} gpio :: [()] -> ([()],[Maybe ()]) gpio i = (i,pure <$> i) {-# NOINLINE gpio #-} ``` Now, when we look at the output of the desugarer (-ddump-ds), we can see that the core-level binder of `topEntity` basically follows the Haskell code. However, when we look at the simplifier output, with nearly all transformations disabled (-O0 -ddump-ds), you will see that parts of `topEntity` are split into 3 different top-level, mutually recursive, functions. So my question are: - Which part of the simplifier is turning these local recursive let-binders into global recursive functions? - Is there some way to disable this transformation? - If not, how much effort do you think it would be to put this behaviour behind a dynflag? So that I, as a GHC API user, can disable it for my use-case. I'm willing to implements this dynflag myself. Kind regards, Christiaan

Christiaan Baaij
Hello GHC Devs,
Hi!
So my question are: - Which part of the simplifier is turning these local recursive let-binders into global recursive functions?
The simplifier does a bit of let floating. See Simplify.simplLazyBind and SimplEnv.doFloatFromRhs. I suspect this is what you are seeing.
- Is there some way to disable this transformation?
You could try adding a flag which is checked by doFloatFromRhs. I'm not sure what, if anything, might break if you do so. Cheers, - Ben

I've created a ticket for this at:
https://ghc.haskell.org/trac/ghc/ticket/13663
On 8 May 2017 at 16:12, Ben Gamari
Christiaan Baaij
writes: Hello GHC Devs,
Hi!
So my question are: - Which part of the simplifier is turning these local recursive let-binders into global recursive functions?
The simplifier does a bit of let floating. See Simplify.simplLazyBind and SimplEnv.doFloatFromRhs. I suspect this is what you are seeing.
- Is there some way to disable this transformation?
You could try adding a flag which is checked by doFloatFromRhs. I'm not sure what, if anything, might break if you do so.
Cheers,
- Ben
participants (2)
-
Ben Gamari
-
Christiaan Baaij