[GHC] #7746: Support loading/unloading profiled objects from a profiled executable

GHC ghc-devs at haskell.org
Fri Sep 6 08:59:59 CEST 2013


#7746: Support loading/unloading profiled objects from a profiled executable
-------------------------------------+------------------------------------
        Reporter:  ezyang            |            Owner:  ezyang
            Type:  feature request   |           Status:  new
        Priority:  normal            |        Milestone:  7.8.1
       Component:  Runtime System    |          Version:  7.7
      Resolution:                    |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:  5435, 8039
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------------
Changes (by ezyang):

 * blockedby:   => 5435, 8039


Old description:

> This is closely related to #3360, but it is a bit less ambitious and
> should be possible to implement without too many extra changes to the
> byte code compiler and interpreter (e.g. we just have to teach the linker
> how to handle things). Here is a simple test program off of 'plugins' to
> get working:
>
> {{{
> {-# LANGUAGE ScopedTypeVariables #-}
>
> import System.Plugins.Make
> import System.Plugins.Load
> import Data.List
>
> boot :: FilePath -> IO ()
> boot path = do
>     r <- make path ["-prof"]
>     case r of
>       MakeSuccess _ p -> do
>         r' <- load p [] [] "result"
>         case r' of
>           LoadSuccess _ (v :: Int) -> print v
>           LoadFailure msg -> print msg
>       MakeFailure es -> putStrLn ("Failed: " ++ intercalate " " es)
>
> main = do
>     boot "Foo.hs"
> }}}
>
> where Foo.hs is
>
> {{{
> module Foo where
> result = 2 :: Int
> }}}
>
> Here are the things that, as far as I can tell, need to be handled:
>
>  * We should ensure consistency between the host and the object file
> being uploaded. For example, if you load an un-profiled object file into
> a profiled binary, GHC will eat all your puppies. A simple way to do this
> is look for a symbol (e.g. CC_LIST) which is only ever exported when
> something is profiled and barf it is encountered.
>
>  * This current code fails with {{{test: Foo.o: unknown symbol
> `CC_LIST'}}}, much the same way GHCi used to fail.  This particular
> problem is (I think) that we don’t store CC_LIST and other externsymbols
> in our global hash table, so the linker thinks that they don’t exist,
> when they do. CC_LIST and friends should be special-cased or added to the
> table.
>
>  * We don’t run ctors which setup CC_LIST with all of the cost-centres
> from the loaded module; we need to teach the linker to do that (that's
> the {{{/* ignore constructor section for now */}}})
>
>  * We need to come up with some sensible way of unloading cost-centres
> from CC_LIST and friends; we could make CC_LIST doubly-linked and then
> just excise the cost-centre in a destructor, but freeing the actual
> allocated CostCentre is more difficult. For now, we might just live with
> the memory leak, but see wiki:"Commentary/ResourceLimits#Memoryleaks" for
> a possible better implementation strategy.
>
> But that’s it; everything else should work normally. Something similar
> should apply to ticky builds. Something we will have to think about is
> how to handle these special-cases as we move from static objects to
> dynamic objects and push more of the runtime linking burden to the
> standard libraries.

New description:

 This is closely related to #3360, but it is a bit less ambitious and
 should be possible to implement without too many extra changes to the byte
 code compiler and interpreter (e.g. we just have to teach the linker how
 to handle things). Here is a simple test program off of 'plugins' to get
 working:

 {{{
 {-# LANGUAGE ScopedTypeVariables #-}

 import System.Plugins.Make
 import System.Plugins.Load
 import Data.List

 boot :: FilePath -> IO ()
 boot path = do
     r <- make path ["-prof"]
     case r of
       MakeSuccess _ p -> do
         r' <- load p [] [] "result"
         case r' of
           LoadSuccess _ (v :: Int) -> print v
           LoadFailure msg -> print msg
       MakeFailure es -> putStrLn ("Failed: " ++ intercalate " " es)

 main = do
     boot "Foo.hs"
 }}}

 where Foo.hs is

 {{{
 module Foo where
 result = 2 :: Int
 }}}

 Here are the things that, as far as I can tell, need to be handled:

  * We should ensure consistency between the host and the object file being
 uploaded. For example, if you load an un-profiled object file into a
 profiled binary, GHC will eat all your puppies. A simple way to do this is
 look for a symbol (e.g. CC_LIST) which is only ever exported when
 something is profiled and barf it is encountered.

  * This current code fails with {{{test: Foo.o: unknown symbol
 `CC_LIST'}}}, much the same way GHCi used to fail.  This particular
 problem is (I think) that we don’t store CC_LIST and other externsymbols
 in our global hash table, so the linker thinks that they don’t exist, when
 they do. CC_LIST and friends should be special-cased or added to the
 table. I have a patch for that; it's pretty easy.

  * We don’t run ctors which setup CC_LIST with all of the cost-centres
 from the loaded module; we need to teach the linker to do that. The
 relevant bug is #5435.

  * We need to come up with some sensible way of unloading cost-centres
 from CC_LIST and friends; we could make CC_LIST doubly-linked and then
 just excise the cost-centre in a destructor, but freeing the actual
 allocated CostCentre is more difficult. For now, we might just live with
 the memory leak, but see wiki:"Commentary/ResourceLimits#Memoryleaks" for
 a possible better implementation strategy. Whatever cleanup is done here
 should be registered as a destructor for the library. Maybe #8039 solves
 this problem.

  * Tests!

 But that’s it; everything else should work normally. Something similar
 should apply to ticky builds. Sans destructors, there is a good chance
 this shindig may already work for dynamically linked apps.

--

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




More information about the ghc-tickets mailing list