[GHC] #10844: CallStack should not be inlined

GHC ghc-devs at haskell.org
Tue Oct 4 13:51:11 UTC 2016


#10844: CallStack should not be inlined
-------------------------------------+-------------------------------------
        Reporter:  nomeata           |                Owner:  gridaphobe
            Type:  task              |               Status:  patch
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.10.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):  Phab:D1259
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by gridaphobe):

 The work in #8472 to float primitive string literals to the top did fix
 the issue I described in https://phabricator.haskell.org/D1259#72921, but
 it turns out there's another issue leading to increased allocations
 elsewhere in nofib. I've minimized the `parstof` benchmark to

 {{{
 module Foo where

 c_the_program=(++) "main ip =\n" ((++) "  i2str (optim (myMain deciem))\n"
 ((++) ";\n" ((++) "\n" ((++) "TYPE tJobdef    = [ JOBDEF, int, int, int,
 tJobdef, tJobdef ] ;\n" ((++) "TYPE tJobstat   = [ JOBSTAT, int, int, int,
 int, tJobdef ] ;\n"
         ((++) "TYPE tTree      = [ LEAF, int |\n" ((++) "
 TREE, tTree, tTree ] ;\n" ((++) "TYPE tProc      = [ PROC, int, tJobstat ]
 ;\n" ((++) "\n" ((++) "\n" ((++) "\n" ((++) "emptyjobdef     = [JOBDEF, 0
 , 0 , 0, emptyjobdef, emptyjobdef] ;\n"  ""))))))))))))
 }}}

 which is just a chain of appends (though the number of `(++)` seems to
 matter!). GHC HEAD optimizes this into a single string literal, whereas my
 patch gives

 {{{
 -- RHS size: {terms: 1, types: 0, coercions: 0}
 Foo.c_the_program11 :: GHC.Prim.Addr#
 [GblId,
  Caf=NoCafRefs,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 120 0}]
 Foo.c_the_program11 =
   "main ip =\n\
   \  i2str (optim (myMain deciem))\n\
   \;\n"#

 -- RHS size: {terms: 1, types: 0, coercions: 0}
 Foo.c_the_program10 :: GHC.Prim.Addr#
 [GblId,
  Caf=NoCafRefs,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 620 0}]
 Foo.c_the_program10 =
   "TYPE tJobdef    = [ JOBDEF, int, int, int, tJobdef, tJobdef ] ;\n\
   \TYPE tJobstat   = [ JOBSTAT, int, int, int, int, tJobdef ] ;\n\
   \TYPE tTree      = [ LEAF, int |\n\
   \                    TREE, tTree, tTree ] ;\n\
   \TYPE tProc      = [ PROC, int, tJobstat ] ;\n"#

 -- RHS size: {terms: 1, types: 0, coercions: 0}
 Foo.c_the_program7 :: GHC.Prim.Addr#
 [GblId,
  Caf=NoCafRefs,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 190 0}]
 Foo.c_the_program7 =
   "emptyjobdef     = [JOBDEF, 0     , 0 , 0, emptyjobdef, emptyjobdef]
 ;\n"#

 -- RHS size: {terms: 2, types: 0, coercions: 0}
 Foo.c_the_program6 :: [Char]
 [GblId,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=True,
          WorkFree=False, Expandable=True, Guidance=IF_ARGS [] 20 0}]
 Foo.c_the_program6 = GHC.CString.unpackCString# Foo.c_the_program7

 -- RHS size: {terms: 3, types: 1, coercions: 0}
 Foo.c_the_program5 :: [Char]
 [GblId,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
          WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 30 0}]
 Foo.c_the_program5 =
   ++ @ Char Foo.c_the_program8 Foo.c_the_program6
 ...
 }}}

 It's able to eliminate some of the `(++)` calls, but not all. I'm not yet
 sure why this is happening, but I imagine it involves a `(++)` term being
 floated out before we eliminate it.

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


More information about the ghc-tickets mailing list