[GHC] #13663: Option to disable turning recursive let-bindings to recursive functions

GHC ghc-devs at haskell.org
Mon May 8 14:16:00 UTC 2017


#13663: Option to disable turning recursive let-bindings to recursive functions
-------------------------------------+-------------------------------------
           Reporter:  darchon        |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 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:

 {{{#!haskell
 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), we can see
 that the core-level binder of `topEntity` basically follows the Haskell
 code.

 {{{#!haskell
 topEntity :: [((), ())]
 [LclIdX]
 topEntity
   = letrec {
       ds_d2rI :: ([()], [Maybe ()])
       [LclId]
       ds_d2rI = gpio (decodeReq 1 req_a2pF);
       ds_d2rS :: ([()], [Maybe ()])
       [LclId]
       ds_d2rS = gpio (decodeReq 2 req_a2pF);
       req_a2pF [Occ=LoopBreaker] :: [()]
       [LclId]
       req_a2pF
         = $ @ 'GHC.Types.LiftedRep
             @ [Maybe ()]
             @ [()]
             core
             (<*>
                @ []
                GHC.Base.$fApplicative[]
                @ (Maybe ())
                @ (Maybe ())
                (<$>
                   @ []
                   @ (Maybe ())
                   @ (Maybe () -> Maybe ())
                   GHC.Base.$fFunctor[]
                   (<|> @ Maybe GHC.Base.$fAlternativeMaybe @ ())
                   (ram (decodeReq 0 req_a2pF)))
                (<*>
                   @ []
                   GHC.Base.$fApplicative[]
                   @ (Maybe ())
                   @ (Maybe ())
                   (<$>
                      @ []
                      @ (Maybe ())
                      @ (Maybe () -> Maybe ())
                      GHC.Base.$fFunctor[]
                      (<|> @ Maybe GHC.Base.$fAlternativeMaybe @ ())
                      (case ds_d2rI of { (_ [Occ=Dead], outResp1_X2pQ) ->
                       outResp1_X2pQ
                       }))
                   (case ds_d2rS of { (_ [Occ=Dead], outResp2_X2q2) ->
                    outResp2_X2q2
                    }))); } in
     <*>
       @ []
       GHC.Base.$fApplicative[]
       @ ()
       @ ((), ())
       (<$>
          @ []
          @ ()
          @ (() -> ((), ()))
          GHC.Base.$fFunctor[]
          (GHC.Tuple.(,) @ () @ ())
          (case ds_d2rI of { (outport1_a2pA, _ [Occ=Dead]) ->
           outport1_a2pA
           }))
       (case ds_d2rS of { (outport2_a2pM, _ [Occ=Dead]) ->
        outport2_a2pM
        })
 }}}

 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.

 {{{#!haskell
 Rec {
 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)

 req_r2sq :: [()]
 req_r2sq
   = core
       (<*>
          @ []
          GHC.Base.$fApplicative[]
          @ (Maybe ())
          @ (Maybe ())
          (<$>
             @ []
             @ (Maybe ())
             @ (Maybe () -> Maybe ())
             GHC.Base.$fFunctor[]
             (<|> @ Maybe GHC.Base.$fAlternativeMaybe @ ())
             (ram (decodeReq 0 req_r2sq)))
          (<*>
             @ []
             GHC.Base.$fApplicative[]
             @ (Maybe ())
             @ (Maybe ())
             (<$>
                @ []
                @ (Maybe ())
                @ (Maybe () -> Maybe ())
                GHC.Base.$fFunctor[]
                (<|> @ Maybe GHC.Base.$fAlternativeMaybe @ ())
                (case ds_r2so of { (outport1_a2pA, outResp1_X2pQ) ->
                 outResp1_X2pQ
                 }))
             (case ds1_r2sp of { (outport2_a2pM, outResp2_X2q2) ->
              outResp2_X2q2
              })))
 end Rec }

 topEntity :: [((), ())]
 topEntity
   = <*>
       @ []
       GHC.Base.$fApplicative[]
       @ ()
       @ ((), ())
       (<$>
          @ []
          @ ()
          @ (() -> ((), ()))
          GHC.Base.$fFunctor[]
          (GHC.Tuple.(,) @ () @ ())
          (case ds_r2so of { (outport1_a2pA, outResp1_X2pQ) ->
           outport1_a2pA
           }))
       (case ds1_r2sp of { (outport2_a2pM, outResp2_X2q2) ->
        outport2_a2pM
        })
 }}}

 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.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13663>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list