Skip to content
Snippets Groups Projects
Commit 4ab7031d authored by Cheng Shao's avatar Cheng Shao :beach: Committed by Torsten Schmits
Browse files

compiler: implement --show-iface-abi-hash major mode

parent 969c9ace
No related branches found
No related tags found
No related merge requests found
......@@ -33,7 +33,7 @@ module GHC.Iface.Load (
WhereFrom(..),
pprModIfaceSimple,
ifaceStats, pprModIface, showIface,
ifaceStats, pprModIface, showIface, showIfaceAbiHash,
module Iface_Errors -- avoids boot files in Ppr modules
) where
......@@ -1090,6 +1090,19 @@ showIface logger dflags unit_state name_cache filename = do
$ withPprStyle (mkDumpStyle name_ppr_ctx)
$ pprModIface unit_state iface
-- | Read binary interface, and print ABI hash. Unlike the
-- @--abi-hash@ major mode, the output is the ABI hash deserialized
-- from the interface directly.
showIfaceAbiHash :: Logger -> DynFlags -> NameCache -> FilePath -> IO ()
showIfaceAbiHash logger dflags name_cache filename = do
let profile = targetProfile dflags
-- skip the hi way check and silence warnings
iface <- readBinIface profile name_cache IgnoreHiWay QuietBinIFace filename
logMsg logger MCDump noSrcSpan
$ ppr $ mi_mod_hash $ mi_final_exts iface
-- | Show a ModIface but don't display details; suitable for ModIfaces stored in
-- the EPT.
pprModIfaceSimple :: UnitState -> ModIface -> SDoc
......
-#include
--abi-hash
--backpack
--show-iface-abi-hash
--show-packages
-Onot
-Walternative-layout-rule-transitional
......
......@@ -291,6 +291,10 @@ main' postLoadMode units dflags0 args flagWarnings = do
(hsc_units hsc_env)
(hsc_NC hsc_env)
f
ShowInterfaceAbiHash f -> liftIO $ showIfaceAbiHash logger
(hsc_dflags hsc_env)
(hsc_NC hsc_env)
f
DoMake -> doMake units srcs
DoMkDependHS -> doMkDependHS (map fst srcs)
StopBefore p -> liftIO (oneShot hsc_env p srcs)
......@@ -481,6 +485,8 @@ isShowGhciUsageMode _ = False
data PostLoadMode
= ShowInterface FilePath -- ghc --show-iface
| ShowInterfaceAbiHash FilePath
-- ghc --show-iface-abi-hash
| DoMkDependHS -- ghc -M
| StopBefore StopPhase -- ghc -E | -C | -S
-- StopBefore StopLn is the default
......@@ -505,6 +511,9 @@ showUnitsMode = mkPostLoadMode ShowPackages
showInterfaceMode :: FilePath -> Mode
showInterfaceMode fp = mkPostLoadMode (ShowInterface fp)
showInterfaceAbiHashMode :: FilePath -> Mode
showInterfaceAbiHashMode fp = mkPostLoadMode (ShowInterfaceAbiHash fp)
stopBeforeMode :: StopPhase -> Mode
stopBeforeMode phase = mkPostLoadMode (StopBefore phase)
......@@ -639,6 +648,9 @@ mode_flags =
[ defFlag "-show-iface" (HasArg (\f -> setMode (showInterfaceMode f)
"--show-iface"))
, defFlag "-show-iface-abi-hash" (HasArg (\f -> setMode (showInterfaceAbiHashMode f)
"--show-iface-abi-hash"))
------- primary modes ------------------------------------------------
, defFlag "c" (PassFlag (\f -> do setMode (stopBeforeMode NoStop) f
addFlag "-no-link" f))
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment