module GHC.Driver.Main
(
newHscEnv
, Messager, batchMsg
, HscStatus (..)
, hscIncrementalCompile
, hscMaybeWriteIface
, hscCompileCmmFile
, hscGenHardCode
, hscInteractive
, hscParse
, hscTypecheckRename
, hscDesugar
, makeSimpleDetails
, hscSimplify
, hscCheckSafe
, hscGetSafe
, hscParseIdentifier
, hscTcRcLookupName
, hscTcRnGetInfo
, hscIsGHCiMonad
, hscGetModuleInterface
, hscRnImportDecls
, hscTcRnLookupRdrName
, hscStmt, hscParseStmtWithLocation, hscStmtWithLocation, hscParsedStmt
, hscDecls, hscParseDeclsWithLocation, hscDeclsWithLocation, hscParsedDecls
, hscTcExpr, TcRnExprMode(..), hscImport, hscKcType
, hscParseExpr
, hscParseType
, hscCompileCoreExpr
, hscCompileCoreExpr'
, hscParse', hscSimplify', hscDesugar', tcRnModule', doCodeGen
, getHscEnv
, hscSimpleIface'
, oneShotMsg
, dumpIfaceStats
, ioMsgMaybe
, showModuleIndex
, hscAddSptEntries
) where
import GHC.Prelude
import GHC.Driver.Plugins
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.Driver.Env
import GHC.Driver.Errors
import GHC.Driver.CodeOutput
import GHC.Driver.Config
import GHC.Driver.Hooks
import GHC.Runtime.Context
import GHC.Runtime.Interpreter ( addSptEntry, hscInterp )
import GHC.Runtime.Loader ( initializePlugins )
import GHCi.RemoteTypes ( ForeignHValue )
import GHC.ByteCode.Types
import GHC.Linker.Loader
import GHC.Linker.Types
import GHC.Hs
import GHC.Hs.Dump
import GHC.Hs.Stats ( ppSourceStats )
import GHC.HsToCore
import GHC.StgToByteCode ( byteCodeGen, stgExprToBCOs )
import GHC.IfaceToCore ( typecheckIface )
import GHC.Iface.Load ( ifaceStats, initExternalPackageState, writeIface )
import GHC.Iface.Make
import GHC.Iface.Recomp
import GHC.Iface.Tidy
import GHC.Iface.Ext.Ast ( mkHieFile )
import GHC.Iface.Ext.Types ( getAsts, hie_asts, hie_module )
import GHC.Iface.Ext.Binary ( readHieFile, writeHieFile , hie_file_result, NameCacheUpdater(..))
import GHC.Iface.Ext.Debug ( diffFile, validateScopes )
import GHC.Iface.Env ( updNameCache )
import GHC.Core
import GHC.Core.Tidy ( tidyExpr )
import GHC.Core.Type ( Type, Kind )
import GHC.Core.Lint ( lintInteractiveExpr )
import GHC.Core.Multiplicity
import GHC.Core.Utils ( exprType )
import GHC.Core.ConLike
import GHC.Core.Opt.Pipeline
import GHC.Core.TyCon
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.CoreToStg.Prep
import GHC.CoreToStg ( coreToStg )
import GHC.Parser.Errors
import GHC.Parser.Errors.Ppr
import GHC.Parser
import GHC.Parser.Lexer as Lexer
import GHC.Tc.Module
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.Zonk ( ZonkFlexi (DefaultFlexi) )
import GHC.Stg.Syntax
import GHC.Stg.FVs ( annTopBindingsFreeVars )
import GHC.Stg.Pipeline ( stg2stg )
import GHC.Builtin.Utils
import GHC.Builtin.Names
import GHC.Builtin.Uniques ( mkPseudoUniqueE )
import qualified GHC.StgToCmm as StgToCmm ( codeGen )
import GHC.StgToCmm.Types (CgInfos (..), ModuleLFInfos)
import GHC.Cmm
import GHC.Cmm.Parser ( parseCmmFile )
import GHC.Cmm.Info.Build
import GHC.Cmm.Pipeline
import GHC.Cmm.Info
import GHC.Unit
import GHC.Unit.External
import GHC.Unit.State
import GHC.Unit.Module.ModDetails
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.Graph
import GHC.Unit.Module.Imported
import GHC.Unit.Module.Deps
import GHC.Unit.Module.Status
import GHC.Unit.Home.ModInfo
import GHC.Types.Id
import GHC.Types.SourceError
import GHC.Types.SafeHaskell
import GHC.Types.ForeignStubs
import GHC.Types.Var.Env ( emptyTidyEnv )
import GHC.Types.Error
import GHC.Types.Fixity.Env
import GHC.Types.CostCentre
import GHC.Types.IPE
import GHC.Types.Unique.Supply
import GHC.Types.SourceFile
import GHC.Types.SrcLoc
import GHC.Types.Name
import GHC.Types.Name.Env
import GHC.Types.Name.Cache ( initNameCache )
import GHC.Types.Name.Reader
import GHC.Types.Name.Ppr
import GHC.Types.TyThing
import GHC.Types.HpcInfo
import GHC.Utils.Fingerprint ( Fingerprint )
import GHC.Utils.Panic
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Exception
import GHC.Utils.Misc
import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Data.FastString
import GHC.Data.Bag
import GHC.Data.StringBuffer
import qualified GHC.Data.Stream as Stream
import GHC.Data.Stream (Stream)
import Data.Data hiding (Fixity, TyCon)
import Data.Maybe ( fromJust )
import Data.List ( nub, isPrefixOf, partition )
import Control.Monad
import Data.IORef
import System.FilePath as FilePath
import System.Directory
import System.IO (fixIO)
import qualified Data.Set as S
import Data.Set (Set)
import Data.Functor
import Control.DeepSeq (force)
import Data.Bifunctor (first, bimap)
#include "HsVersions.h"
newHscEnv :: DynFlags -> IO HscEnv
newHscEnv dflags = do
eps_var <- newIORef initExternalPackageState
us <- mkSplitUniqSupply 'r'
nc_var <- newIORef (initNameCache us knownKeyNames)
fc_var <- newIORef emptyInstalledModuleEnv
logger <- initLogger
tmpfs <- initTmpFs
return HscEnv { hsc_dflags = dflags
, hsc_logger = logger
, hsc_targets = []
, hsc_mod_graph = emptyMG
, hsc_IC = emptyInteractiveContext dflags
, hsc_HPT = emptyHomePackageTable
, hsc_EPS = eps_var
, hsc_NC = nc_var
, hsc_FC = fc_var
, hsc_type_env_var = Nothing
, hsc_interp = Nothing
, hsc_unit_env = panic "hsc_unit_env not initialized"
, hsc_plugins = []
, hsc_static_plugins = []
, hsc_unit_dbs = Nothing
, hsc_hooks = emptyHooks
, hsc_tmpfs = tmpfs
}
getWarnings :: Hsc WarningMessages
getWarnings = Hsc $ \_ w -> return (w, w)
clearWarnings :: Hsc ()
clearWarnings = Hsc $ \_ _ -> return ((), emptyBag)
logWarnings :: WarningMessages -> Hsc ()
logWarnings w = Hsc $ \_ w0 -> return ((), w0 `unionBags` w)
getHscEnv :: Hsc HscEnv
getHscEnv = Hsc $ \e w -> return (e, w)
handleWarnings :: Hsc ()
handleWarnings = do
dflags <- getDynFlags
logger <- getLogger
w <- getWarnings
liftIO $ printOrThrowWarnings logger dflags w
clearWarnings
logWarningsReportErrors :: (Bag PsWarning, Bag PsError) -> Hsc ()
logWarningsReportErrors (warnings,errors) = do
let warns = fmap pprWarning warnings
errs = fmap pprError errors
logWarnings warns
when (not $ isEmptyBag errs) $ throwErrors errs
handleWarningsThrowErrors :: (Bag PsWarning, Bag PsError) -> Hsc a
handleWarningsThrowErrors (warnings, errors) = do
let warns = fmap pprWarning warnings
errs = fmap pprError errors
logWarnings warns
dflags <- getDynFlags
logger <- getLogger
(wWarns, wErrs) <- warningsToMessages dflags <$> getWarnings
liftIO $ printBagOfErrors logger dflags wWarns
throwErrors (unionBags errs wErrs)
ioMsgMaybe :: IO (Messages DecoratedSDoc, Maybe a) -> Hsc a
ioMsgMaybe ioA = do
(msgs, mb_r) <- liftIO ioA
let (warns, errs) = partitionMessages msgs
logWarnings warns
case mb_r of
Nothing -> throwErrors errs
Just r -> ASSERT( isEmptyBag errs ) return r
ioMsgMaybe' :: IO (Messages DecoratedSDoc, Maybe a) -> Hsc (Maybe a)
ioMsgMaybe' ioA = do
(msgs, mb_r) <- liftIO $ ioA
logWarnings (getWarningMessages msgs)
return mb_r
hscTcRnLookupRdrName :: HscEnv -> LocatedN RdrName -> IO [Name]
hscTcRnLookupRdrName hsc_env0 rdr_name
= runInteractiveHsc hsc_env0 $
do { hsc_env <- getHscEnv
; ioMsgMaybe $ tcRnLookupRdrName hsc_env rdr_name }
hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
hscTcRcLookupName hsc_env0 name = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
ioMsgMaybe' $ tcRnLookupName hsc_env name
hscTcRnGetInfo :: HscEnv -> Name
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
hscTcRnGetInfo hsc_env0 name
= runInteractiveHsc hsc_env0 $
do { hsc_env <- getHscEnv
; ioMsgMaybe' $ tcRnGetInfo hsc_env name }
hscIsGHCiMonad :: HscEnv -> String -> IO Name
hscIsGHCiMonad hsc_env name
= runHsc hsc_env $ ioMsgMaybe $ isGHCiMonad hsc_env name
hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
hscGetModuleInterface hsc_env0 mod = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
ioMsgMaybe $ getModuleInterface hsc_env mod
hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv
hscRnImportDecls hsc_env0 import_decls = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
ioMsgMaybe $ tcRnImportDecls hsc_env import_decls
hscParse :: HscEnv -> ModSummary -> IO HsParsedModule
hscParse hsc_env mod_summary = runHsc hsc_env $ hscParse' mod_summary
hscParse' :: ModSummary -> Hsc HsParsedModule
hscParse' mod_summary
| Just r <- ms_parsed_mod mod_summary = return r
| otherwise = do
dflags <- getDynFlags
logger <- getLogger
withTiming logger dflags
(text "Parser"<+>brackets (ppr $ ms_mod mod_summary))
(const ()) $ do
let src_filename = ms_hspp_file mod_summary
maybe_src_buf = ms_hspp_buf mod_summary
buf <- case maybe_src_buf of
Just b -> return b
Nothing -> liftIO $ hGetStringBuffer src_filename
let loc = mkRealSrcLoc (mkFastString src_filename) 1 1
let parseMod | HsigFile == ms_hsc_src mod_summary
= parseSignature
| otherwise = parseModule
case unP parseMod (initParserState (initParserOpts dflags) buf loc) of
PFailed pst ->
handleWarningsThrowErrors (getMessages pst)
POk pst rdr_module -> do
let (warns, errs) = bimap (fmap pprWarning) (fmap pprError) (getMessages pst)
logWarnings warns
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed "Parser"
FormatHaskell (ppr rdr_module)
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed_ast "Parser AST"
FormatHaskell (showAstData NoBlankSrcSpan
NoBlankEpAnnotations
rdr_module)
liftIO $ dumpIfSet_dyn logger dflags Opt_D_source_stats "Source Statistics"
FormatText (ppSourceStats False rdr_module)
when (not $ isEmptyBag errs) $ throwErrors errs
let n_hspp = FilePath.normalise src_filename
srcs0 = nub $ filter (not . (tmpDir dflags `isPrefixOf`))
$ filter (not . (== n_hspp))
$ map FilePath.normalise
$ filter (not . isPrefixOf "<")
$ map unpackFS
$ srcfiles pst
srcs1 = case ml_hs_file (ms_location mod_summary) of
Just f -> filter (/= FilePath.normalise f) srcs0
Nothing -> srcs0
srcs2 <- liftIO $ filterM doesFileExist srcs1
let res = HsParsedModule {
hpm_module = rdr_module,
hpm_src_files = srcs2
}
let applyPluginAction p opts
= parsedResultAction p opts mod_summary
hsc_env <- getHscEnv
withPlugins hsc_env applyPluginAction res
extract_renamed_stuff :: ModSummary -> TcGblEnv -> Hsc RenamedStuff
extract_renamed_stuff mod_summary tc_result = do
let rn_info = getRenamedStuff tc_result
dflags <- getDynFlags
logger <- getLogger
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_rn_ast "Renamer"
FormatHaskell (showAstData NoBlankSrcSpan NoBlankEpAnnotations rn_info)
when (gopt Opt_WriteHie dflags) $ do
hieFile <- mkHieFile mod_summary tc_result (fromJust rn_info)
let out_file = ml_hie_file $ ms_location mod_summary
liftIO $ writeHieFile out_file hieFile
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_hie "HIE AST" FormatHaskell (ppr $ hie_asts hieFile)
when (gopt Opt_ValidateHie dflags) $ do
hs_env <- Hsc $ \e w -> return (e, w)
liftIO $ do
case validateScopes (hie_module hieFile) $ getAsts $ hie_asts hieFile of
[] -> putMsg logger dflags $ text "Got valid scopes"
xs -> do
putMsg logger dflags $ text "Got invalid scopes"
mapM_ (putMsg logger dflags) xs
file' <- readHieFile (NCU $ updNameCache $ hsc_NC hs_env) out_file
case diffFile hieFile (hie_file_result file') of
[] ->
putMsg logger dflags $ text "Got no roundtrip errors"
xs -> do
putMsg logger dflags $ text "Got roundtrip errors"
mapM_ (putMsg logger (dopt_set dflags Opt_D_ppr_debug)) xs
return rn_info
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule
-> IO (TcGblEnv, RenamedStuff)
hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $
hsc_typecheck True mod_summary (Just rdr_module)
hsc_typecheck :: Bool
-> ModSummary -> Maybe HsParsedModule
-> Hsc (TcGblEnv, RenamedStuff)
hsc_typecheck keep_rn mod_summary mb_rdr_module = do
hsc_env <- getHscEnv
let hsc_src = ms_hsc_src mod_summary
dflags = hsc_dflags hsc_env
home_unit = hsc_home_unit hsc_env
outer_mod = ms_mod mod_summary
mod_name = moduleName outer_mod
outer_mod' = mkHomeModule home_unit mod_name
inner_mod = homeModuleNameInstantiation home_unit mod_name
src_filename = ms_hspp_file mod_summary
real_loc = realSrcLocSpan $ mkRealSrcLoc (mkFastString src_filename) 1 1
keep_rn' = gopt Opt_WriteHie dflags || keep_rn
MASSERT( isHomeModule home_unit outer_mod )
tc_result <- if hsc_src == HsigFile && not (isHoleModule inner_mod)
then ioMsgMaybe $ tcRnInstantiateSignature hsc_env outer_mod' real_loc
else
do hpm <- case mb_rdr_module of
Just hpm -> return hpm
Nothing -> hscParse' mod_summary
tc_result0 <- tcRnModule' mod_summary keep_rn' hpm
if hsc_src == HsigFile
then do (iface, _, _) <- liftIO $ hscSimpleIface hsc_env tc_result0 Nothing
ioMsgMaybe $
tcRnMergeSignatures hsc_env hpm tc_result0 iface
else return tc_result0
rn_info <- extract_renamed_stuff mod_summary tc_result
return (tc_result, rn_info)
tcRnModule' :: ModSummary -> Bool -> HsParsedModule
-> Hsc TcGblEnv
tcRnModule' sum save_rn_syntax mod = do
hsc_env <- getHscEnv
dflags <- getDynFlags
when (not (safeHaskellModeEnabled dflags)
&& wopt Opt_WarnMissingSafeHaskellMode dflags) $
logWarnings $ unitBag $
makeIntoWarning (Reason Opt_WarnMissingSafeHaskellMode) $
mkPlainWarnMsg (getLoc (hpm_module mod)) $
warnMissingSafeHaskellMode
tcg_res <-
ioMsgMaybe $
tcRnModule hsc_env sum
save_rn_syntax mod
(tcSafeOK, whyUnsafe) <- liftIO $ readIORef (tcg_safeInfer tcg_res)
let allSafeOK = safeInferred dflags && tcSafeOK
if not (safeHaskellOn dflags)
|| (safeInferOn dflags && not allSafeOK)
then markUnsafeInfer tcg_res whyUnsafe
else do
tcg_res' <- hscCheckSafeImports tcg_res
safe <- liftIO $ fst <$> readIORef (tcg_safeInfer tcg_res')
when safe $
case wopt Opt_WarnSafe dflags of
True
| safeHaskell dflags == Sf_Safe -> return ()
| otherwise -> (logWarnings $ unitBag $
makeIntoWarning (Reason Opt_WarnSafe) $
mkPlainWarnMsg (warnSafeOnLoc dflags) $
errSafe tcg_res')
False | safeHaskell dflags == Sf_Trustworthy &&
wopt Opt_WarnTrustworthySafe dflags ->
(logWarnings $ unitBag $
makeIntoWarning (Reason Opt_WarnTrustworthySafe) $
mkPlainWarnMsg (trustworthyOnLoc dflags) $
errTwthySafe tcg_res')
False -> return ()
return tcg_res'
where
pprMod t = ppr $ moduleName $ tcg_mod t
errSafe t = quotes (pprMod t) <+> text "has been inferred as safe!"
errTwthySafe t = quotes (pprMod t)
<+> text "is marked as Trustworthy but has been inferred as safe!"
warnMissingSafeHaskellMode = ppr (moduleName (ms_mod sum))
<+> text "is missing Safe Haskell mode"
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
hscDesugar hsc_env mod_summary tc_result =
runHsc hsc_env $ hscDesugar' (ms_location mod_summary) tc_result
hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' mod_location tc_result = do
hsc_env <- getHscEnv
r <- ioMsgMaybe $
deSugar hsc_env mod_location tc_result
handleWarnings
return r
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails hsc_env tc_result = mkBootModDetailsTc hsc_env tc_result
type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
hscIncrementalFrontend :: Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int,Int)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
hscIncrementalFrontend
always_do_basic_recompilation_check m_tc_result
mHscMessage mod_summary source_modified mb_old_iface mod_index
= do
hsc_env <- getHscEnv
let msg what = case mHscMessage of
Just hscMessage -> hscMessage hsc_env mod_index what (ModuleNode (extendModSummaryNoDeps mod_summary))
Nothing -> return ()
skip iface = do
liftIO $ msg UpToDate
return $ Left iface
compile mb_old_hash reason = do
liftIO $ msg reason
tc_result <- case hscFrontendHook (hsc_hooks hsc_env) of
Nothing -> FrontendTypecheck . fst <$> hsc_typecheck False mod_summary Nothing
Just h -> h mod_summary
return $ Right (tc_result, mb_old_hash)
stable = case source_modified of
SourceUnmodifiedAndStable -> True
_ -> False
case m_tc_result of
Just tc_result
| not always_do_basic_recompilation_check ->
return $ Right (FrontendTypecheck tc_result, Nothing)
_ -> do
(recomp_reqd, mb_checked_iface)
<-
liftIO $ checkOldIface hsc_env mod_summary
source_modified mb_old_iface
let mb_old_hash = fmap (mi_iface_hash . mi_final_exts) mb_checked_iface
case mb_checked_iface of
Just iface | not (recompileRequired recomp_reqd) ->
case m_tc_result of
Nothing
| mi_used_th iface && not stable ->
compile mb_old_hash (RecompBecause "TH")
_ ->
skip iface
_ ->
case m_tc_result of
Nothing -> compile mb_old_hash recomp_reqd
Just tc_result ->
return $ Right (FrontendTypecheck tc_result, mb_old_hash)
hscIncrementalCompile :: Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int,Int)
-> IO (HscStatus, HscEnv)
hscIncrementalCompile always_do_basic_recompilation_check m_tc_result
mHscMessage hsc_env' mod_summary source_modified mb_old_iface mod_index
= do
hsc_env'' <- initializePlugins hsc_env'
type_env_var <- newIORef emptyNameEnv
let mod = ms_mod mod_summary
hsc_env | isOneShot (ghcMode (hsc_dflags hsc_env''))
= hsc_env'' { hsc_type_env_var = Just (mod, type_env_var) }
| otherwise
= hsc_env''
runHsc hsc_env $ do
e <- hscIncrementalFrontend always_do_basic_recompilation_check m_tc_result mHscMessage
mod_summary source_modified mb_old_iface mod_index
case e of
Left iface -> do
details <- liftIO . fixIO $ \details' -> do
let hsc_env' =
hsc_env {
hsc_HPT = addToHpt (hsc_HPT hsc_env)
(ms_mod_name mod_summary) (HomeModInfo iface details' Nothing)
}
genModDetails hsc_env' iface
return (HscUpToDate iface details, hsc_env')
Right (FrontendTypecheck tc_result, mb_old_hash) -> do
status <- finish mod_summary tc_result mb_old_hash
return (status, hsc_env)
finish :: ModSummary
-> TcGblEnv
-> Maybe Fingerprint
-> Hsc HscStatus
finish summary tc_result mb_old_hash = do
hsc_env <- getHscEnv
dflags <- getDynFlags
logger <- getLogger
let bcknd = backend dflags
hsc_src = ms_hsc_src summary
mb_desugar <-
if ms_mod summary /= gHC_PRIM && hsc_src == HsSrcFile
then Just <$> hscDesugar' (ms_location summary) tc_result
else pure Nothing
case mb_desugar of
Just desugared_guts | bcknd /= NoBackend -> do
plugins <- liftIO $ readIORef (tcg_th_coreplugins tc_result)
simplified_guts <- hscSimplify' plugins desugared_guts
(cg_guts, details) <-
liftIO $ tidyProgram hsc_env simplified_guts
let !partial_iface =
force (mkPartialIface hsc_env details simplified_guts)
return HscRecomp { hscs_guts = cg_guts,
hscs_mod_location = ms_location summary,
hscs_mod_details = details,
hscs_partial_iface = partial_iface,
hscs_old_iface_hash = mb_old_hash
}
_ -> do
(iface, mb_old_iface_hash, details) <- liftIO $
hscSimpleIface hsc_env tc_result mb_old_hash
liftIO $ hscMaybeWriteIface logger dflags True iface mb_old_iface_hash (ms_location summary)
return $ case bcknd of
NoBackend -> HscNotGeneratingCode iface details
_ -> case hsc_src of
HsBootFile -> HscUpdateBoot iface details
HsigFile -> HscUpdateSig iface details
_ -> panic "finish"
hscMaybeWriteIface :: Logger -> DynFlags -> Bool -> ModIface -> Maybe Fingerprint -> ModLocation -> IO ()
hscMaybeWriteIface logger dflags is_simple iface old_iface mod_location = do
let force_write_interface = gopt Opt_WriteInterface dflags
write_interface = case backend dflags of
NoBackend -> False
Interpreter -> False
_ -> True
baseName = ml_hi_file mod_location
buildIfName suffix
| Just name <- outputHi dflags
= name
| otherwise
= let with_hi = replaceExtension baseName suffix
in addBootSuffix_maybe (mi_boot iface) with_hi
write_iface dflags' iface =
let !iface_name = buildIfName (hiSuf dflags')
in
withTiming logger dflags'
(text "WriteIface"<+>brackets (text iface_name))
(const ())
(writeIface logger dflags' iface_name iface)
when (write_interface || force_write_interface) $ do
let no_change = old_iface == Just (mi_iface_hash (mi_final_exts iface))
dt <- dynamicTooState dflags
when (dopt Opt_D_dump_if_trace dflags) $ putMsg logger dflags $
hang (text "Writing interface(s):") 2 $ vcat
[ text "Kind:" <+> if is_simple then text "simple" else text "full"
, text "Hash change:" <+> ppr (not no_change)
, text "DynamicToo state:" <+> text (show dt)
]
if is_simple
then unless no_change $ do
write_iface dflags iface
case dt of
DT_Dont -> return ()
DT_Failed -> return ()
DT_Dyn -> panic "Unexpected DT_Dyn state when writing simple interface"
DT_OK -> write_iface (setDynamicNow dflags) iface
else case dt of
DT_Dont | not no_change -> write_iface dflags iface
DT_OK | not no_change -> write_iface dflags iface
DT_Dyn -> write_iface dflags iface
DT_Failed | not (dynamicNow dflags) -> write_iface dflags iface
_ -> return ()
genModDetails :: HscEnv -> ModIface -> IO ModDetails
genModDetails hsc_env old_iface
= do
new_details <-
initIfaceLoad hsc_env (typecheckIface old_iface)
dumpIfaceStats hsc_env
return new_details
oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
oneShotMsg hsc_env recomp =
case recomp of
UpToDate ->
compilationProgressMsg logger dflags $
text "compilation IS NOT required"
_ ->
return ()
where
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
batchMsg :: Messager
batchMsg hsc_env mod_index recomp node = case node of
InstantiationNode _ ->
case recomp of
MustCompile -> showMsg (text "Instantiating ") empty
UpToDate
| verbosity dflags >= 2 -> showMsg (text "Skipping ") empty
| otherwise -> return ()
RecompBecause reason -> showMsg (text "Instantiating ") (text " [" <> text reason <> text "]")
ModuleNode _ ->
case recomp of
MustCompile -> showMsg (text "Compiling ") empty
UpToDate
| verbosity dflags >= 2 -> showMsg (text "Skipping ") empty
| otherwise -> return ()
RecompBecause reason -> showMsg (text "Compiling ") (text " [" <> text reason <> text "]")
where
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
showMsg msg reason =
compilationProgressMsg logger dflags $
(showModuleIndex mod_index <>
msg <> showModMsg dflags (recompileRequired recomp) node)
<> reason
hscCheckSafeImports :: TcGblEnv -> Hsc TcGblEnv
hscCheckSafeImports tcg_env = do
dflags <- getDynFlags
tcg_env' <- checkSafeImports tcg_env
checkRULES dflags tcg_env'
where
checkRULES dflags tcg_env' =
case safeLanguageOn dflags of
True -> do
logWarnings $ warns (tcg_rules tcg_env')
return tcg_env' { tcg_rules = [] }
False
| safeInferOn dflags && not (null $ tcg_rules tcg_env')
-> markUnsafeInfer tcg_env' $ warns (tcg_rules tcg_env')
| otherwise
-> return tcg_env'
warns rules = listToBag $ map warnRules rules
warnRules :: LRuleDecl GhcTc -> MsgEnvelope DecoratedSDoc
warnRules (L loc (HsRule { rd_name = n })) =
mkPlainWarnMsg (locA loc) $
text "Rule \"" <> ftext (snd $ unLoc n) <> text "\" ignored" $+$
text "User defined rules are disabled under Safe Haskell"
checkSafeImports :: TcGblEnv -> Hsc TcGblEnv
checkSafeImports tcg_env
= do
dflags <- getDynFlags
imps <- mapM condense imports'
let (safeImps, regImps) = partition (\(_,_,s) -> s) imps
oldErrs <- getWarnings
clearWarnings
safePkgs <- S.fromList <$> mapMaybeM checkSafe safeImps
safeErrs <- getWarnings
clearWarnings
(infErrs, infPkgs) <- case (safeInferOn dflags) of
False -> return (emptyBag, S.empty)
True -> do infPkgs <- S.fromList <$> mapMaybeM checkSafe regImps
infErrs <- getWarnings
clearWarnings
return (infErrs, infPkgs)
logWarnings oldErrs
case (isEmptyBag safeErrs) of
False -> liftIO . throwIO . mkSrcErr $ safeErrs
True -> do
let infPassed = isEmptyBag infErrs
tcg_env' <- case (not infPassed) of
True -> markUnsafeInfer tcg_env infErrs
False -> return tcg_env
when (packageTrustOn dflags) $ checkPkgTrust pkgReqs
let newTrust = pkgTrustReqs dflags safePkgs infPkgs infPassed
return tcg_env' { tcg_imports = impInfo `plusImportAvails` newTrust }
where
impInfo = tcg_imports tcg_env
imports = imp_mods impInfo
imports1 = moduleEnvToList imports
imports' = map (fmap importedByUser) imports1
pkgReqs = imp_trust_pkgs impInfo
condense :: (Module, [ImportedModsVal]) -> Hsc (Module, SrcSpan, IsSafeImport)
condense (_, []) = panic "GHC.Driver.Main.condense: Pattern match failure!"
condense (m, x:xs) = do imv <- foldlM cond' x xs
return (m, imv_span imv, imv_is_safe imv)
cond' :: ImportedModsVal -> ImportedModsVal -> Hsc ImportedModsVal
cond' v1 v2
| imv_is_safe v1 /= imv_is_safe v2
= throwOneError $ mkPlainMsgEnvelope (imv_span v1)
(text "Module" <+> ppr (imv_name v1) <+>
(text $ "is imported both as a safe and unsafe import!"))
| otherwise
= return v1
checkSafe :: (Module, SrcSpan, a) -> Hsc (Maybe UnitId)
checkSafe (m, l, _) = fst `fmap` hscCheckSafe' m l
pkgTrustReqs :: DynFlags -> Set UnitId -> Set UnitId ->
Bool -> ImportAvails
pkgTrustReqs dflags req inf infPassed | safeInferOn dflags
&& not (safeHaskellModeEnabled dflags) && infPassed
= emptyImportAvails {
imp_trust_pkgs = req `S.union` inf
}
pkgTrustReqs dflags _ _ _ | safeHaskell dflags == Sf_Unsafe
= emptyImportAvails
pkgTrustReqs _ req _ _ = emptyImportAvails { imp_trust_pkgs = req }
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool
hscCheckSafe hsc_env m l = runHsc hsc_env $ do
dflags <- getDynFlags
pkgs <- snd `fmap` hscCheckSafe' m l
when (packageTrustOn dflags) $ checkPkgTrust pkgs
errs <- getWarnings
return $ isEmptyBag errs
hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, Set UnitId)
hscGetSafe hsc_env m l = runHsc hsc_env $ do
(self, pkgs) <- hscCheckSafe' m l
good <- isEmptyBag `fmap` getWarnings
clearWarnings
let pkgs' | Just p <- self = S.insert p pkgs
| otherwise = pkgs
return (good, pkgs')
hscCheckSafe' :: Module -> SrcSpan
-> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' m l = do
hsc_env <- getHscEnv
let home_unit = hsc_home_unit hsc_env
(tw, pkgs) <- isModSafe home_unit m l
case tw of
False -> return (Nothing, pkgs)
True | isHomeModule home_unit m -> return (Nothing, pkgs)
| otherwise -> return (Just $ toUnitId (moduleUnit m), pkgs)
where
isModSafe :: HomeUnit -> Module -> SrcSpan -> Hsc (Bool, Set UnitId)
isModSafe home_unit m l = do
hsc_env <- getHscEnv
dflags <- getDynFlags
iface <- lookup' m
case iface of
Nothing -> throwOneError $ mkPlainMsgEnvelope l
$ text "Can't load the interface file for" <+> ppr m
<> text ", to check that it can be safely imported"
Just iface' ->
let trust = getSafeMode $ mi_trust iface'
trust_own_pkg = mi_trust_pkg iface'
safeM = trust `elem` [Sf_Safe, Sf_SafeInferred, Sf_Trustworthy]
safeP = packageTrusted dflags (hsc_units hsc_env) home_unit trust trust_own_pkg m
pkgRs = S.fromList . map fst $ filter snd $ dep_pkgs $ mi_deps iface'
warns = if wopt Opt_WarnInferredSafeImports dflags
&& safeLanguageOn dflags
&& trust == Sf_SafeInferred
then inferredImportWarn
else emptyBag
errs = case (safeM, safeP) of
(True, True ) -> emptyBag
(True, False) -> pkgTrustErr
(False, _ ) -> modTrustErr
in do
logWarnings warns
logWarnings errs
return (trust == Sf_Trustworthy, pkgRs)
where
state = hsc_units hsc_env
inferredImportWarn = unitBag
$ makeIntoWarning (Reason Opt_WarnInferredSafeImports)
$ mkWarnMsg l (pkgQual state)
$ sep
[ text "Importing Safe-Inferred module "
<> ppr (moduleName m)
<> text " from explicitly Safe module"
]
pkgTrustErr = unitBag $ mkMsgEnvelope l (pkgQual state) $
sep [ ppr (moduleName m)
<> text ": Can't be safely imported!"
, text "The package ("
<> (pprWithUnitState state $ ppr (moduleUnit m))
<> text ") the module resides in isn't trusted."
]
modTrustErr = unitBag $ mkMsgEnvelope l (pkgQual state) $
sep [ ppr (moduleName m)
<> text ": Can't be safely imported!"
, text "The module itself isn't safe." ]
packageTrusted :: DynFlags -> UnitState -> HomeUnit -> SafeHaskellMode -> Bool -> Module -> Bool
packageTrusted dflags unit_state home_unit safe_mode trust_own_pkg mod =
case safe_mode of
Sf_None -> False
Sf_Ignore -> False
Sf_Unsafe -> False
_ | not (packageTrustOn dflags) -> True
Sf_Safe | not trust_own_pkg -> True
Sf_SafeInferred | not trust_own_pkg -> True
_ | isHomeModule home_unit mod -> True
_ -> unitIsTrusted $ unsafeLookupUnit unit_state (moduleUnit m)
lookup' :: Module -> Hsc (Maybe ModIface)
lookup' m = do
hsc_env <- getHscEnv
hsc_eps <- liftIO $ hscEPS hsc_env
let pkgIfaceT = eps_PIT hsc_eps
homePkgT = hsc_HPT hsc_env
iface = lookupIfaceByModule homePkgT pkgIfaceT m
case iface of
Just _ -> return iface
Nothing -> snd `fmap` (liftIO $ getModuleInterface hsc_env m)
checkPkgTrust :: Set UnitId -> Hsc ()
checkPkgTrust pkgs = do
hsc_env <- getHscEnv
let errors = S.foldr go [] pkgs
state = hsc_units hsc_env
go pkg acc
| unitIsTrusted $ unsafeLookupUnitId state pkg
= acc
| otherwise
= (:acc) $ mkMsgEnvelope noSrcSpan (pkgQual state)
$ pprWithUnitState state
$ text "The package ("
<> ppr pkg
<> text ") is required to be trusted but it isn't!"
case errors of
[] -> return ()
_ -> (liftIO . throwIO . mkSrcErr . listToBag) errors
markUnsafeInfer :: TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer tcg_env whyUnsafe = do
dflags <- getDynFlags
when (wopt Opt_WarnUnsafe dflags)
(logWarnings $ unitBag $ makeIntoWarning (Reason Opt_WarnUnsafe) $
mkPlainWarnMsg (warnUnsafeOnLoc dflags) (whyUnsafe' dflags))
liftIO $ writeIORef (tcg_safeInfer tcg_env) (False, whyUnsafe)
case not (safeHaskellModeEnabled dflags) of
True -> return $ tcg_env { tcg_imports = wiped_trust }
False -> return tcg_env
where
wiped_trust = (tcg_imports tcg_env) { imp_trust_pkgs = S.empty }
pprMod = ppr $ moduleName $ tcg_mod tcg_env
whyUnsafe' df = vcat [ quotes pprMod <+> text "has been inferred as unsafe!"
, text "Reason:"
, nest 4 $ (vcat $ badFlags df) $+$
(vcat $ pprMsgEnvelopeBagWithLoc whyUnsafe) $+$
(vcat $ badInsts $ tcg_insts tcg_env)
]
badFlags df = concatMap (badFlag df) unsafeFlagsForInfer
badFlag df (str,loc,on,_)
| on df = [mkLocMessage SevOutput (loc df) $
text str <+> text "is not allowed in Safe Haskell"]
| otherwise = []
badInsts insts = concatMap badInst insts
checkOverlap (NoOverlap _) = False
checkOverlap _ = True
badInst ins | checkOverlap (overlapMode (is_flag ins))
= [mkLocMessage SevOutput (nameSrcSpan $ getName $ is_dfun ins) $
ppr (overlapMode $ is_flag ins) <+>
text "overlap mode isn't allowed in Safe Haskell"]
| otherwise = []
hscGetSafeMode :: TcGblEnv -> Hsc SafeHaskellMode
hscGetSafeMode tcg_env = do
dflags <- getDynFlags
liftIO $ finalSafeMode dflags tcg_env
hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts
hscSimplify hsc_env plugins modguts =
runHsc hsc_env $ hscSimplify' plugins modguts
hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts
hscSimplify' plugins ds_result = do
hsc_env <- getHscEnv
hsc_env_with_plugins <- if null plugins
then return hsc_env
else liftIO $ initializePlugins $ hsc_env
{ hsc_dflags = foldr addPluginModuleName (hsc_dflags hsc_env) plugins
}
liftIO $ core2core hsc_env_with_plugins ds_result
hscSimpleIface :: HscEnv
-> TcGblEnv
-> Maybe Fingerprint
-> IO (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface hsc_env tc_result mb_old_iface
= runHsc hsc_env $ hscSimpleIface' tc_result mb_old_iface
hscSimpleIface' :: TcGblEnv
-> Maybe Fingerprint
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface' tc_result mb_old_iface = do
hsc_env <- getHscEnv
details <- liftIO $ mkBootModDetailsTc hsc_env tc_result
safe_mode <- hscGetSafeMode tc_result
new_iface
<-
liftIO $
mkIfaceTc hsc_env safe_mode details tc_result
liftIO $ dumpIfaceStats hsc_env
return (new_iface, mb_old_iface, details)
hscGenHardCode :: HscEnv -> CgGuts -> ModLocation -> FilePath
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)], CgInfos)
hscGenHardCode hsc_env cgguts location output_filename = do
let CgGuts{
cg_module = this_mod,
cg_binds = core_binds,
cg_tycons = tycons,
cg_foreign = foreign_stubs0,
cg_foreign_files = foreign_files,
cg_dep_pkgs = dependencies,
cg_hpc_info = hpc_info } = cgguts
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
hooks = hsc_hooks hsc_env
tmpfs = hsc_tmpfs hsc_env
data_tycons = filter isDataTyCon tycons
(prepd_binds, local_ccs) <-
corePrepPgm hsc_env this_mod location
core_binds data_tycons
(stg_binds, denv, (caf_ccs, caf_cc_stacks))
<-
withTiming logger dflags
(text "CoreToStg"<+>brackets (ppr this_mod))
(\(a, b, (c,d)) -> a `seqList` b `seq` c `seqList` d `seqList` ())
(myCoreToStg logger dflags (hsc_IC hsc_env) this_mod location prepd_binds)
let cost_centre_info =
(S.toList local_ccs ++ caf_ccs, caf_cc_stacks)
platform = targetPlatform dflags
prof_init
| sccProfilingEnabled dflags = profilingInitCode platform this_mod cost_centre_info
| otherwise = mempty
withTiming logger dflags
(text "CodeGen"<+>brackets (ppr this_mod))
(const ()) $ do
cmms <-
doCodeGen hsc_env this_mod denv data_tycons
cost_centre_info
stg_binds hpc_info
rawcmms0 <-
case cmmToRawCmmHook hooks of
Nothing -> cmmToRawCmm logger dflags cmms
Just h -> h dflags (Just this_mod) cmms
let dump a = do
unless (null a) $
dumpIfSet_dyn logger dflags Opt_D_dump_cmm_raw "Raw Cmm" FormatCMM (pdoc platform a)
return a
rawcmms1 = Stream.mapM dump rawcmms0
let foreign_stubs st = foreign_stubs0 `appendStubC` prof_init
`appendStubC` cgIPEStub st
(output_filename, (_stub_h_exists, stub_c_exists), foreign_fps, cg_infos)
<-
codeOutput logger tmpfs dflags (hsc_units hsc_env) this_mod output_filename location
foreign_stubs foreign_files dependencies rawcmms1
return (output_filename, stub_c_exists, foreign_fps, cg_infos)
hscInteractive :: HscEnv
-> CgGuts
-> ModLocation
-> IO (Maybe FilePath, CompiledByteCode, [SptEntry])
hscInteractive hsc_env cgguts location = do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
let tmpfs = hsc_tmpfs hsc_env
let CgGuts{
cg_module = this_mod,
cg_binds = core_binds,
cg_tycons = tycons,
cg_foreign = foreign_stubs,
cg_modBreaks = mod_breaks,
cg_spt_entries = spt_entries } = cgguts
data_tycons = filter isDataTyCon tycons
(prepd_binds, _) <-
corePrepPgm hsc_env this_mod location core_binds data_tycons
(stg_binds, _infotable_prov, _caf_ccs__caf_cc_stacks)
<-
myCoreToStg logger dflags (hsc_IC hsc_env) this_mod location prepd_binds
comp_bc <- byteCodeGen hsc_env this_mod stg_binds data_tycons mod_breaks
(_istub_h_exists, istub_c_exists)
<- outputForeignStubs logger tmpfs dflags (hsc_units hsc_env) this_mod location foreign_stubs
return (istub_c_exists, comp_bc, spt_entries)
hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO (Maybe FilePath)
hscCompileCmmFile hsc_env filename output_filename = runHsc hsc_env $ do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
let hooks = hsc_hooks hsc_env
let tmpfs = hsc_tmpfs hsc_env
home_unit = hsc_home_unit hsc_env
platform = targetPlatform dflags
mod_name = mkModuleName $ "Cmm$" ++ FilePath.takeFileName filename
cmm_mod = mkHomeModule home_unit mod_name
(cmm, ents) <- ioMsgMaybe
$ do
(warns,errs,cmm) <- withTiming logger dflags (text "ParseCmm"<+>brackets (text filename)) (\_ -> ())
$ parseCmmFile dflags cmm_mod home_unit filename
return (mkMessages (fmap pprWarning warns `unionBags` fmap pprError errs), cmm)
liftIO $ do
dumpIfSet_dyn logger dflags Opt_D_dump_cmm_verbose_by_proc "Parsed Cmm" FormatCMM (pdoc platform cmm)
cmmgroup <-
concatMapM (\cmm -> snd <$> cmmPipeline hsc_env (emptySRT cmm_mod) [cmm]) cmm
unless (null cmmgroup) $
dumpIfSet_dyn logger dflags Opt_D_dump_cmm "Output Cmm"
FormatCMM (pdoc platform cmmgroup)
rawCmms <- case cmmToRawCmmHook hooks of
Nothing -> cmmToRawCmm logger dflags (Stream.yield cmmgroup)
Just h -> h dflags Nothing (Stream.yield cmmgroup)
let foreign_stubs _ =
let ip_init = ipInitCode dflags cmm_mod ents
in NoStubs `appendStubC` ip_init
(_output_filename, (_stub_h_exists, stub_c_exists), _foreign_fps, _caf_infos)
<- codeOutput logger tmpfs dflags (hsc_units hsc_env) cmm_mod output_filename no_loc foreign_stubs [] []
rawCmms
return stub_c_exists
where
no_loc = ModLocation{ ml_hs_file = Just filename,
ml_hi_file = panic "hscCompileCmmFile: no hi file",
ml_obj_file = panic "hscCompileCmmFile: no obj file",
ml_hie_file = panic "hscCompileCmmFile: no hie file"}
doCodeGen :: HscEnv -> Module -> InfoTableProvMap -> [TyCon]
-> CollectedCCs
-> [StgTopBinding]
-> HpcInfo
-> IO (Stream IO CmmGroupSRTs CgInfos)
doCodeGen hsc_env this_mod denv data_tycons
cost_centre_info stg_binds hpc_info = do
let dflags = hsc_dflags hsc_env
let logger = hsc_logger hsc_env
let hooks = hsc_hooks hsc_env
let tmpfs = hsc_tmpfs hsc_env
let platform = targetPlatform dflags
let stg_binds_w_fvs = annTopBindingsFreeVars stg_binds
dumpIfSet_dyn logger dflags Opt_D_dump_stg_final "Final STG:" FormatSTG (pprGenStgTopBindings (initStgPprOpts dflags) stg_binds_w_fvs)
let stg_to_cmm = case stgToCmmHook hooks of
Nothing -> StgToCmm.codeGen logger tmpfs
Just h -> h
let cmm_stream :: Stream IO CmmGroup (CStub, ModuleLFInfos)
cmm_stream = stg_binds_w_fvs `seqList`
stg_to_cmm dflags this_mod denv data_tycons cost_centre_info stg_binds_w_fvs hpc_info
let dump1 a = do
unless (null a) $
dumpIfSet_dyn logger dflags Opt_D_dump_cmm_from_stg
"Cmm produced by codegen" FormatCMM (pdoc platform a)
return a
ppr_stream1 = Stream.mapM dump1 cmm_stream
pipeline_stream :: Stream IO CmmGroupSRTs CgInfos
pipeline_stream = do
(non_cafs, (used_info, lf_infos)) <-
Stream.mapAccumL_ (cmmPipeline hsc_env) (emptySRT this_mod) ppr_stream1
<&> first (srtMapNonCAFs . moduleSRTMap)
return CgInfos{ cgNonCafs = non_cafs, cgLFInfos = lf_infos, cgIPEStub = used_info }
dump2 a = do
unless (null a) $
dumpIfSet_dyn logger dflags Opt_D_dump_cmm "Output Cmm" FormatCMM (pdoc platform a)
return a
return (Stream.mapM dump2 pipeline_stream)
myCoreToStgExpr :: Logger -> DynFlags -> InteractiveContext
-> Module -> ModLocation -> CoreExpr
-> IO ( StgRhs
, InfoTableProvMap
, CollectedCCs )
myCoreToStgExpr logger dflags ictxt this_mod ml prepd_expr = do
let bco_tmp_id = mkSysLocal (fsLit "BCO_toplevel")
(mkPseudoUniqueE 0)
Many
(exprType prepd_expr)
([StgTopLifted (StgNonRec _ stg_expr)], prov_map, collected_ccs) <-
myCoreToStg logger
dflags
ictxt
this_mod
ml
[NonRec bco_tmp_id prepd_expr]
return (stg_expr, prov_map, collected_ccs)
myCoreToStg :: Logger -> DynFlags -> InteractiveContext
-> Module -> ModLocation -> CoreProgram
-> IO ( [StgTopBinding]
, InfoTableProvMap
, CollectedCCs )
myCoreToStg logger dflags ictxt this_mod ml prepd_binds = do
let (stg_binds, denv, cost_centre_info)
=
coreToStg dflags this_mod ml prepd_binds
stg_binds2
<-
stg2stg logger dflags ictxt this_mod stg_binds
return (stg_binds2, denv, cost_centre_info)
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscStmt hsc_env stmt = hscStmtWithLocation hsc_env stmt "<interactive>" 1
hscStmtWithLocation :: HscEnv
-> String
-> String
-> Int
-> IO ( Maybe ([Id]
, ForeignHValue
, FixityEnv))
hscStmtWithLocation hsc_env0 stmt source linenumber =
runInteractiveHsc hsc_env0 $ do
maybe_stmt <- hscParseStmtWithLocation source linenumber stmt
case maybe_stmt of
Nothing -> return Nothing
Just parsed_stmt -> do
hsc_env <- getHscEnv
liftIO $ hscParsedStmt hsc_env parsed_stmt
hscParsedStmt :: HscEnv
-> GhciLStmt GhcPs
-> IO ( Maybe ([Id]
, ForeignHValue
, FixityEnv))
hscParsedStmt hsc_env stmt = runInteractiveHsc hsc_env $ do
(ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt hsc_env stmt
ds_expr <- ioMsgMaybe $ deSugarExpr hsc_env tc_expr
liftIO (lintInteractiveExpr (text "desugar expression") hsc_env ds_expr)
handleWarnings
let src_span = srcLocSpan interactiveSrcLoc
hval <- liftIO $ hscCompileCoreExpr hsc_env src_span ds_expr
return $ Just (ids, hval, fix_env)
hscDecls :: HscEnv
-> String
-> IO ([TyThing], InteractiveContext)
hscDecls hsc_env str = hscDeclsWithLocation hsc_env str "<interactive>" 1
hscParseDeclsWithLocation :: HscEnv -> String -> Int -> String -> IO [LHsDecl GhcPs]
hscParseDeclsWithLocation hsc_env source line_num str = do
L _ (HsModule{ hsmodDecls = decls }) <-
runInteractiveHsc hsc_env $
hscParseThingWithLocation source line_num parseModule str
return decls
hscDeclsWithLocation :: HscEnv
-> String
-> String
-> Int
-> IO ([TyThing], InteractiveContext)
hscDeclsWithLocation hsc_env str source linenumber = do
L _ (HsModule{ hsmodDecls = decls }) <-
runInteractiveHsc hsc_env $
hscParseThingWithLocation source linenumber parseModule str
hscParsedDecls hsc_env decls
hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
hsc_env <- getHscEnv
let interp = hscInterp hsc_env
tc_gblenv <- ioMsgMaybe $ tcRnDeclsi hsc_env decls
let defaults = tcg_default tc_gblenv
let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing,
ml_hi_file = panic "hsDeclsWithLocation:ml_hi_file",
ml_obj_file = panic "hsDeclsWithLocation:ml_obj_file",
ml_hie_file = panic "hsDeclsWithLocation:ml_hie_file" }
ds_result <- hscDesugar' iNTERACTIVELoc tc_gblenv
simpl_mg <- liftIO $ do
plugins <- readIORef (tcg_th_coreplugins tc_gblenv)
hscSimplify hsc_env plugins ds_result
(tidy_cg, mod_details) <- liftIO $ tidyProgram hsc_env simpl_mg
let !CgGuts{ cg_module = this_mod,
cg_binds = core_binds,
cg_tycons = tycons,
cg_modBreaks = mod_breaks } = tidy_cg
!ModDetails { md_insts = cls_insts
, md_fam_insts = fam_insts } = mod_details
data_tycons = filter isDataTyCon tycons
(prepd_binds, _) <-
liftIO $ corePrepPgm hsc_env this_mod iNTERACTIVELoc core_binds data_tycons
(stg_binds, _infotable_prov, _caf_ccs__caf_cc_stacks)
<-
liftIO $ myCoreToStg (hsc_logger hsc_env)
(hsc_dflags hsc_env)
(hsc_IC hsc_env)
this_mod
iNTERACTIVELoc
prepd_binds
cbc <- liftIO $ byteCodeGen hsc_env this_mod
stg_binds data_tycons mod_breaks
let src_span = srcLocSpan interactiveSrcLoc
liftIO $ loadDecls interp hsc_env src_span cbc
liftIO $ hscAddSptEntries hsc_env (cg_spt_entries tidy_cg)
let tcs = filterOut isImplicitTyCon (mg_tcs simpl_mg)
patsyns = mg_patsyns simpl_mg
ext_ids = [ id | id <- bindersOfBinds core_binds
, isExternalName (idName id)
, not (isDFunId id || isImplicitId id) ]
new_tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns
ictxt = hsc_IC hsc_env
fix_env = tcg_fix_env tc_gblenv
new_ictxt = extendInteractiveContext ictxt new_tythings cls_insts
fam_insts defaults fix_env
return (new_tythings, new_ictxt)
hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
hscAddSptEntries hsc_env entries = do
let interp = hscInterp hsc_env
let add_spt_entry :: SptEntry -> IO ()
add_spt_entry (SptEntry i fpr) = do
val <- loadName interp hsc_env (idName i)
addSptEntry interp fpr val
mapM_ add_spt_entry entries
hscImport :: HscEnv -> String -> IO (ImportDecl GhcPs)
hscImport hsc_env str = runInteractiveHsc hsc_env $ do
(L _ (HsModule{hsmodImports=is})) <-
hscParseThing parseModule str
case is of
[L _ i] -> return i
_ -> liftIO $ throwOneError $
mkPlainMsgEnvelope noSrcSpan $
text "parse error in import declaration"
hscTcExpr :: HscEnv
-> TcRnExprMode
-> String
-> IO Type
hscTcExpr hsc_env0 mode expr = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
parsed_expr <- hscParseExpr expr
ioMsgMaybe $ tcRnExpr hsc_env mode parsed_expr
hscKcType
:: HscEnv
-> Bool
-> String
-> IO (Type, Kind)
hscKcType hsc_env0 normalise str = runInteractiveHsc hsc_env0 $ do
hsc_env <- getHscEnv
ty <- hscParseType str
ioMsgMaybe $ tcRnType hsc_env DefaultFlexi normalise ty
hscParseExpr :: String -> Hsc (LHsExpr GhcPs)
hscParseExpr expr = do
maybe_stmt <- hscParseStmt expr
case maybe_stmt of
Just (L _ (BodyStmt _ expr _ _)) -> return expr
_ -> throwOneError $ mkPlainMsgEnvelope noSrcSpan
(text "not an expression:" <+> quotes (text expr))
hscParseStmt :: String -> Hsc (Maybe (GhciLStmt GhcPs))
hscParseStmt = hscParseThing parseStmt
hscParseStmtWithLocation :: String -> Int -> String
-> Hsc (Maybe (GhciLStmt GhcPs))
hscParseStmtWithLocation source linenumber stmt =
hscParseThingWithLocation source linenumber parseStmt stmt
hscParseType :: String -> Hsc (LHsType GhcPs)
hscParseType = hscParseThing parseType
hscParseIdentifier :: HscEnv -> String -> IO (LocatedN RdrName)
hscParseIdentifier hsc_env str =
runInteractiveHsc hsc_env $ hscParseThing parseIdentifier str
hscParseThing :: (Outputable thing, Data thing)
=> Lexer.P thing -> String -> Hsc thing
hscParseThing = hscParseThingWithLocation "<interactive>" 1
hscParseThingWithLocation :: (Outputable thing, Data thing) => String -> Int
-> Lexer.P thing -> String -> Hsc thing
hscParseThingWithLocation source linenumber parser str = do
dflags <- getDynFlags
logger <- getLogger
withTiming logger dflags
(text "Parser [source]")
(const ()) $ do
let buf = stringToStringBuffer str
loc = mkRealSrcLoc (fsLit source) linenumber 1
case unP parser (initParserState (initParserOpts dflags) buf loc) of
PFailed pst ->
handleWarningsThrowErrors (getMessages pst)
POk pst thing -> do
logWarningsReportErrors (getMessages pst)
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed "Parser"
FormatHaskell (ppr thing)
liftIO $ dumpIfSet_dyn logger dflags Opt_D_dump_parsed_ast "Parser AST"
FormatHaskell (showAstData NoBlankSrcSpan NoBlankEpAnnotations thing)
return thing
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr hsc_env loc expr =
case hscCompileCoreExprHook (hsc_hooks hsc_env) of
Nothing -> hscCompileCoreExpr' hsc_env loc expr
Just h -> h hsc_env loc expr
hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr' hsc_env srcspan ds_expr
= do {
simpl_expr <- simplifyExpr hsc_env ds_expr
; let tidy_expr = tidyExpr emptyTidyEnv simpl_expr
; prepd_expr <- corePrepExpr hsc_env tidy_expr
; lintInteractiveExpr (text "hscCompileExpr") hsc_env prepd_expr
; let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing,
ml_hi_file = panic "hscCompileCoreExpr':ml_hi_file",
ml_obj_file = panic "hscCompileCoreExpr':ml_obj_file",
ml_hie_file = panic "hscCompileCoreExpr':ml_hie_file" }
; let ictxt = hsc_IC hsc_env
; (stg_expr, _, _) <-
myCoreToStgExpr (hsc_logger hsc_env)
(hsc_dflags hsc_env)
ictxt
(icInteractiveModule ictxt)
iNTERACTIVELoc
prepd_expr
; bcos <- stgExprToBCOs hsc_env
(icInteractiveModule ictxt)
(exprType prepd_expr)
stg_expr
; loadExpr (hscInterp hsc_env) hsc_env srcspan bcos }
dumpIfaceStats :: HscEnv -> IO ()
dumpIfaceStats hsc_env = do
eps <- readIORef (hsc_EPS hsc_env)
dumpIfSet logger dflags (dump_if_trace || dump_rn_stats)
"Interface statistics"
(ifaceStats eps)
where
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
dump_rn_stats = dopt Opt_D_dump_rn_stats dflags
dump_if_trace = dopt Opt_D_dump_if_trace dflags
showModuleIndex :: (Int, Int) -> SDoc
showModuleIndex (i,n) = text "[" <> pad <> int i <> text " of " <> int n <> text "] "
where
len x = ceiling (logBase 10 (fromIntegral x+1) :: Float)
pad = text (replicate (len n len i) ' ')