Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,333
    • Issues 4,333
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 370
    • Merge Requests 370
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #13663

Closed
Open
Opened May 08, 2017 by darchon@trac-darchon

Option to disable turning recursive let-bindings to recursive functions

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:

module Test where

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)

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 -dsuppress-all), we can see that the core-level binder of topEntity basically follows the Haskell code.

topEntity :: [((), ())]
topEntity
  = letrec {
      ds_d2rI :: ([()], [Maybe ()])
      ds_d2rI = gpio (decodeReq 1 req_a2pG);
      ds_d2rS :: ([()], [Maybe ()])
      ds_d2rS = gpio (decodeReq 2 req_a2pG);
      req_a2pG :: [()]
      req_a2pG
        = $ core
            (<*>
               $fApplicative[]
               (<$>
                  $fFunctor[] (<|> $fAlternativeMaybe) (ram (decodeReq 0 req_a2pG)))
               (<*>
                  $fApplicative[]
                  (<$>
                     $fFunctor[]
                     (<|> $fAlternativeMaybe)
                     (case ds_d2rI of { (_, outResp1_X2pR) -> outResp1_X2pR }))
                  (case ds_d2rS of { (_, outResp2_X2q3) -> outResp2_X2q3 }))); } in
    <*>
      $fApplicative[]
      (<$>
         $fFunctor[]
         (,)
         (case ds_d2rI of { (outport1_a2pB, _) -> outport1_a2pB }))
      (case ds_d2rS of { (outport2_a2pN, _) -> outport2_a2pN })

However, when we look at the simplifier output, with nearly all transformations disabled (-O0 -ddump-simpl -dsuppress-all), you will see that parts of topEntity are split into 3 different top-level, mutually recursive, functions.

Rec {
-- RHS size: {terms: 4, types: 0, coercions: 0, joins: 0/0}
ds_r2so :: ([()], [Maybe ()])
ds_r2so = gpio (decodeReq 1 req_r2sq)

-- RHS size: {terms: 4, types: 0, coercions: 0, joins: 0/0}
ds1_r2sp :: ([()], [Maybe ()])
ds1_r2sp = gpio (decodeReq 2 req_r2sq)

-- RHS size: {terms: 25, types: 50, coercions: 0, joins: 0/0}
req_r2sq :: [()]
req_r2sq
  = core
      (<*>
         $fApplicative[]
         (<$>
            $fFunctor[] (<|> $fAlternativeMaybe) (ram (decodeReq 0 req_r2sq)))
         (<*>
            $fApplicative[]
            (<$>
               $fFunctor[]
               (<|> $fAlternativeMaybe)
               (case ds_r2so of { (outport1_a2pB, outResp1_X2pR) ->
                outResp1_X2pR
                }))
            (case ds1_r2sp of { (outport2_a2pN, outResp2_X2q3) ->
             outResp2_X2q3
             })))
end Rec }

-- RHS size: {terms: 13, types: 35, coercions: 0, joins: 0/0}
topEntity :: [((), ())]
topEntity
  = <*>
      $fApplicative[]
      (<$>
         $fFunctor[]
         (,)
         (case ds_r2so of { (outport1_a2pB, outResp1_X2pR) ->
          outport1_a2pB
          }))
      (case ds1_r2sp of { (outport2_a2pN, outResp2_X2q3) ->
       outport2_a2pN
       })

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.
Edited Mar 10, 2019 by darchon
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#13663