Matthew Pickering pushed to branch wip/bytecode-library at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Linker/ByteCode.hs
    1
    +-- Utilities for creating bytecode libraries
    
    2
    +module GHC.Linker.ByteCode where
    
    3
    +
    
    4
    +import GHC.Prelude
    
    5
    +import GHC.ByteCode.Serialize
    
    6
    +import GHC.Driver.Session
    
    7
    +import GHC.Utils.Error
    
    8
    +import GHC.Driver.Env
    
    9
    +import GHC.Utils.Outputable
    
    10
    +
    
    11
    +
    
    12
    +linkBytecodeLib :: HscEnv -> [ByteCodeObject] -> IO ()
    
    13
    +linkBytecodeLib hsc_env gbcs = do
    
    14
    +  let dflags = hsc_dflags hsc_env
    
    15
    +  -- The .gbc files from the command line
    
    16
    +  let bytecodeObjects = [f | FileOption _ f <- ldInputs dflags]
    
    17
    +
    
    18
    +  -- INSERT_YOUR_CODE
    
    19
    +  let logger = hsc_logger hsc_env
    
    20
    +  let allFiles = (map text bytecodeObjects) ++ [ angleBrackets (text "in-memory" <+>  ppr (bco_module bco)) | bco <- gbcs ]
    
    21
    +  debugTraceMsg logger 2 $
    
    22
    +    text "linkBytecodeLib: linking the following bytecode objects:" $$
    
    23
    +    vcat allFiles
    
    24
    +
    
    25
    +  bytecodeLib <- mkBytecodeLib hsc_env bytecodeObjects gbcs
    
    26
    +  let output_fn = case outputFile dflags of { Just s -> s; Nothing -> "a.out"; }
    
    27
    +  writeBytecodeLib bytecodeLib output_fn
    
    28
    +  return ()
    
    29
    +