{-# LANGUAGE BangPatterns, CPP, MagicHash, NondecreasingIndentation #-}
{-# OPTIONS_GHC -fprof-auto-top #-}
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 Data.Data hiding (Fixity, TyCon)
import Data.Maybe ( fromJust )
import GHC.Types.Id
import GHC.Runtime.Interpreter ( addSptEntry )
import GHCi.RemoteTypes ( ForeignHValue )
import GHC.CoreToByteCode ( byteCodeGen, coreExprToBCOs )
import GHC.Runtime.Linker
import GHC.Core.Tidy ( tidyExpr )
import GHC.Core.Type ( Type, Kind )
import GHC.Core.Lint ( lintInteractiveExpr )
import GHC.Types.Var.Env ( emptyTidyEnv )
import GHC.Utils.Panic
import GHC.Core.ConLike
import GHC.Parser.Annotation
import GHC.Unit.Module
import GHC.Unit.State
import GHC.Types.Name.Reader
import GHC.Hs
import GHC.Hs.Dump
import GHC.Core
import GHC.Data.StringBuffer
import GHC.Parser
import GHC.Parser.Lexer as Lexer
import GHC.Types.SrcLoc
import GHC.Tc.Module
import GHC.IfaceToCore ( typecheckIface )
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.Zonk ( ZonkFlexi (DefaultFlexi) )
import GHC.Types.Name.Cache ( initNameCache )
import GHC.Builtin.Utils
import GHC.Core.Opt.Driver
import GHC.HsToCore
import GHC.Iface.Load ( ifaceStats, initExternalPackageState, writeIface )
import GHC.Iface.Make
import GHC.Iface.Recomp
import GHC.Iface.Tidy
import GHC.CoreToStg.Prep
import GHC.CoreToStg ( coreToStg )
import GHC.Stg.Syntax
import GHC.Stg.FVs ( annTopBindingsFreeVars )
import GHC.Stg.Pipeline ( stg2stg )
import qualified GHC.StgToCmm as StgToCmm ( codeGen )
import GHC.Types.CostCentre
import GHC.Core.TyCon
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Cmm
import GHC.Cmm.Parser ( parseCmmFile )
import GHC.Cmm.Info.Build
import GHC.Cmm.Pipeline
import GHC.Cmm.Info
import GHC.Driver.CodeOutput
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.Utils.Fingerprint ( Fingerprint )
import GHC.Driver.Hooks
import GHC.Tc.Utils.Env
import GHC.Builtin.Names
import GHC.Driver.Plugins
import GHC.Runtime.Loader ( initializePlugins )
import GHC.Driver.Session
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Types.Name.Env
import GHC.Hs.Stats ( ppSourceStats )
import GHC.Driver.Types
import GHC.Data.FastString
import GHC.Types.Unique.Supply
import GHC.Data.Bag
import GHC.Utils.Exception
import qualified GHC.Data.Stream as Stream
import GHC.Data.Stream (Stream)
import GHC.Utils.Misc
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.Map as M
import qualified Data.Set as S
import Data.Set (Set)
import Data.Functor
import Control.DeepSeq (force)
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 )
#include "HsVersions.h"
newHscEnv :: DynFlags -> IO HscEnv
newHscEnv :: DynFlags -> IO HscEnv
newHscEnv DynFlags
dflags = do
IORef ExternalPackageState
eps_var <- ExternalPackageState -> IO (IORef ExternalPackageState)
forall a. a -> IO (IORef a)
newIORef ExternalPackageState
initExternalPackageState
UniqSupply
us <- Char -> IO UniqSupply
mkSplitUniqSupply Char
'r'
IORef NameCache
nc_var <- NameCache -> IO (IORef NameCache)
forall a. a -> IO (IORef a)
newIORef (UniqSupply -> [Name] -> NameCache
initNameCache UniqSupply
us [Name]
knownKeyNames)
IORef (InstalledModuleEnv InstalledFindResult)
fc_var <- InstalledModuleEnv InstalledFindResult
-> IO (IORef (InstalledModuleEnv InstalledFindResult))
forall a. a -> IO (IORef a)
newIORef InstalledModuleEnv InstalledFindResult
forall a. InstalledModuleEnv a
emptyInstalledModuleEnv
DynLinker
emptyDynLinker <- IO DynLinker
uninitializedLinker
HscEnv -> IO HscEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return HscEnv :: DynFlags
-> [Target]
-> ModuleGraph
-> InteractiveContext
-> HomePackageTable
-> IORef ExternalPackageState
-> IORef NameCache
-> IORef (InstalledModuleEnv InstalledFindResult)
-> Maybe (Module, IORef TypeEnv)
-> Maybe Interp
-> DynLinker
-> HscEnv
HscEnv { hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags
, hsc_targets :: [Target]
hsc_targets = []
, hsc_mod_graph :: ModuleGraph
hsc_mod_graph = ModuleGraph
emptyMG
, hsc_IC :: InteractiveContext
hsc_IC = DynFlags -> InteractiveContext
emptyInteractiveContext DynFlags
dflags
, hsc_HPT :: HomePackageTable
hsc_HPT = HomePackageTable
emptyHomePackageTable
, hsc_EPS :: IORef ExternalPackageState
hsc_EPS = IORef ExternalPackageState
eps_var
, hsc_NC :: IORef NameCache
hsc_NC = IORef NameCache
nc_var
, hsc_FC :: IORef (InstalledModuleEnv InstalledFindResult)
hsc_FC = IORef (InstalledModuleEnv InstalledFindResult)
fc_var
, hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
hsc_type_env_var = Maybe (Module, IORef TypeEnv)
forall a. Maybe a
Nothing
, hsc_interp :: Maybe Interp
hsc_interp = Maybe Interp
forall a. Maybe a
Nothing
, hsc_dynLinker :: DynLinker
hsc_dynLinker = DynLinker
emptyDynLinker
}
getWarnings :: Hsc WarningMessages
getWarnings :: Hsc WarningMessages
getWarnings = (HscEnv
-> WarningMessages -> IO (WarningMessages, WarningMessages))
-> Hsc WarningMessages
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv
-> WarningMessages -> IO (WarningMessages, WarningMessages))
-> Hsc WarningMessages)
-> (HscEnv
-> WarningMessages -> IO (WarningMessages, WarningMessages))
-> Hsc WarningMessages
forall a b. (a -> b) -> a -> b
$ \HscEnv
_ WarningMessages
w -> (WarningMessages, WarningMessages)
-> IO (WarningMessages, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (WarningMessages
w, WarningMessages
w)
clearWarnings :: Hsc ()
clearWarnings :: Hsc ()
clearWarnings = (HscEnv -> WarningMessages -> IO ((), WarningMessages)) -> Hsc ()
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO ((), WarningMessages)) -> Hsc ())
-> (HscEnv -> WarningMessages -> IO ((), WarningMessages))
-> Hsc ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
_ WarningMessages
_ -> ((), WarningMessages) -> IO ((), WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ((), WarningMessages
forall a. Bag a
emptyBag)
logWarnings :: WarningMessages -> Hsc ()
logWarnings :: WarningMessages -> Hsc ()
logWarnings WarningMessages
w = (HscEnv -> WarningMessages -> IO ((), WarningMessages)) -> Hsc ()
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO ((), WarningMessages)) -> Hsc ())
-> (HscEnv -> WarningMessages -> IO ((), WarningMessages))
-> Hsc ()
forall a b. (a -> b) -> a -> b
$ \HscEnv
_ WarningMessages
w0 -> ((), WarningMessages) -> IO ((), WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ((), WarningMessages
w0 WarningMessages -> WarningMessages -> WarningMessages
forall a. Bag a -> Bag a -> Bag a
`unionBags` WarningMessages
w)
getHscEnv :: Hsc HscEnv
getHscEnv :: Hsc HscEnv
getHscEnv = (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv)
-> (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a b. (a -> b) -> a -> b
$ \HscEnv
e WarningMessages
w -> (HscEnv, WarningMessages) -> IO (HscEnv, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (HscEnv
e, WarningMessages
w)
handleWarnings :: Hsc ()
handleWarnings :: Hsc ()
handleWarnings = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
WarningMessages
w <- Hsc WarningMessages
getWarnings
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> WarningMessages -> IO ()
printOrThrowWarnings DynFlags
dflags WarningMessages
w
Hsc ()
clearWarnings
logWarningsReportErrors :: Messages -> Hsc ()
logWarningsReportErrors :: (WarningMessages, WarningMessages) -> Hsc ()
logWarningsReportErrors (WarningMessages
warns,WarningMessages
errs) = do
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (IsSafeImport -> IsSafeImport
not (IsSafeImport -> IsSafeImport) -> IsSafeImport -> IsSafeImport
forall a b. (a -> b) -> a -> b
$ WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag WarningMessages
errs) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ WarningMessages -> Hsc ()
forall (io :: * -> *) a. MonadIO io => WarningMessages -> io a
External instance of the constraint type MonadIO Hsc
throwErrors WarningMessages
errs
handleWarningsThrowErrors :: Messages -> Hsc a
handleWarningsThrowErrors :: (WarningMessages, WarningMessages) -> Hsc a
handleWarningsThrowErrors (WarningMessages
warns, WarningMessages
errs) = do
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
(WarningMessages
wWarns, WarningMessages
wErrs) <- DynFlags -> WarningMessages -> (WarningMessages, WarningMessages)
warningsToMessages DynFlags
dflags (WarningMessages -> (WarningMessages, WarningMessages))
-> Hsc WarningMessages -> Hsc (WarningMessages, WarningMessages)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
<$> Hsc WarningMessages
getWarnings
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> WarningMessages -> IO ()
printBagOfErrors DynFlags
dflags WarningMessages
wWarns
WarningMessages -> Hsc a
forall (io :: * -> *) a. MonadIO io => WarningMessages -> io a
External instance of the constraint type MonadIO Hsc
throwErrors (WarningMessages -> WarningMessages -> WarningMessages
forall a. Bag a -> Bag a -> Bag a
unionBags WarningMessages
errs WarningMessages
wErrs)
ioMsgMaybe :: IO (Messages, Maybe a) -> Hsc a
ioMsgMaybe :: IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe IO ((WarningMessages, WarningMessages), Maybe a)
ioA = do
((WarningMessages
warns,WarningMessages
errs), Maybe a
mb_r) <- IO ((WarningMessages, WarningMessages), Maybe a)
-> Hsc ((WarningMessages, WarningMessages), Maybe a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO IO ((WarningMessages, WarningMessages), Maybe a)
ioA
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
case Maybe a
mb_r of
Maybe a
Nothing -> WarningMessages -> Hsc a
forall (io :: * -> *) a. MonadIO io => WarningMessages -> io a
External instance of the constraint type MonadIO Hsc
throwErrors WarningMessages
errs
Just a
r -> ASSERT( isEmptyBag errs ) return r
ioMsgMaybe' :: IO (Messages, Maybe a) -> Hsc (Maybe a)
ioMsgMaybe' :: IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc (Maybe a)
ioMsgMaybe' IO ((WarningMessages, WarningMessages), Maybe a)
ioA = do
((WarningMessages
warns,WarningMessages
_errs), Maybe a
mb_r) <- IO ((WarningMessages, WarningMessages), Maybe a)
-> Hsc ((WarningMessages, WarningMessages), Maybe a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ((WarningMessages, WarningMessages), Maybe a)
-> Hsc ((WarningMessages, WarningMessages), Maybe a))
-> IO ((WarningMessages, WarningMessages), Maybe a)
-> Hsc ((WarningMessages, WarningMessages), Maybe a)
forall a b. (a -> b) -> a -> b
$ IO ((WarningMessages, WarningMessages), Maybe a)
ioA
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
Maybe a -> Hsc (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return Maybe a
mb_r
hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name]
hscTcRnLookupRdrName :: HscEnv -> Located RdrName -> IO [Name]
hscTcRnLookupRdrName HscEnv
hsc_env0 Located RdrName
rdr_name
= HscEnv -> Hsc [Name] -> IO [Name]
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc [Name] -> IO [Name]) -> Hsc [Name] -> IO [Name]
forall a b. (a -> b) -> a -> b
$
do { HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
; IO ((WarningMessages, WarningMessages), Maybe [Name]) -> Hsc [Name]
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe [Name])
-> Hsc [Name])
-> IO ((WarningMessages, WarningMessages), Maybe [Name])
-> Hsc [Name]
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Located RdrName
-> IO ((WarningMessages, WarningMessages), Maybe [Name])
tcRnLookupRdrName HscEnv
hsc_env Located RdrName
rdr_name }
hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
hscTcRcLookupName :: HscEnv -> Name -> IO (Maybe TyThing)
hscTcRcLookupName HscEnv
hsc_env0 Name
name = HscEnv -> Hsc (Maybe TyThing) -> IO (Maybe TyThing)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc (Maybe TyThing) -> IO (Maybe TyThing))
-> Hsc (Maybe TyThing) -> IO (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
IO ((WarningMessages, WarningMessages), Maybe TyThing)
-> Hsc (Maybe TyThing)
forall a.
IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc (Maybe a)
ioMsgMaybe' (IO ((WarningMessages, WarningMessages), Maybe TyThing)
-> Hsc (Maybe TyThing))
-> IO ((WarningMessages, WarningMessages), Maybe TyThing)
-> Hsc (Maybe TyThing)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Name -> IO ((WarningMessages, WarningMessages), Maybe TyThing)
tcRnLookupName HscEnv
hsc_env Name
name
hscTcRnGetInfo :: HscEnv -> Name
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
hscTcRnGetInfo :: HscEnv
-> Name -> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
hscTcRnGetInfo HscEnv
hsc_env0 Name
name
= HscEnv
-> Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)))
-> Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> IO (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
forall a b. (a -> b) -> a -> b
$
do { HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
; IO
((WarningMessages, WarningMessages),
Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
forall a.
IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc (Maybe a)
ioMsgMaybe' (IO
((WarningMessages, WarningMessages),
Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)))
-> IO
((WarningMessages, WarningMessages),
Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
-> Hsc (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Name
-> IO
((WarningMessages, WarningMessages),
Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
tcRnGetInfo HscEnv
hsc_env Name
name }
hscIsGHCiMonad :: HscEnv -> String -> IO Name
hscIsGHCiMonad :: HscEnv -> String -> IO Name
hscIsGHCiMonad HscEnv
hsc_env String
name
= HscEnv -> Hsc Name -> IO Name
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc Name -> IO Name) -> Hsc Name -> IO Name
forall a b. (a -> b) -> a -> b
$ IO ((WarningMessages, WarningMessages), Maybe Name) -> Hsc Name
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe Name) -> Hsc Name)
-> IO ((WarningMessages, WarningMessages), Maybe Name) -> Hsc Name
forall a b. (a -> b) -> a -> b
$ HscEnv
-> String -> IO ((WarningMessages, WarningMessages), Maybe Name)
isGHCiMonad HscEnv
hsc_env String
name
hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
hscGetModuleInterface :: HscEnv -> Module -> IO ModIface
hscGetModuleInterface HscEnv
hsc_env0 Module
mod = HscEnv -> Hsc ModIface -> IO ModIface
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc ModIface -> IO ModIface) -> Hsc ModIface -> IO ModIface
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ModIface
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ModIface)
-> IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ModIface
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Module
-> IO ((WarningMessages, WarningMessages), Maybe ModIface)
getModuleInterface HscEnv
hsc_env Module
mod
hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv
hscRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO GlobalRdrEnv
hscRnImportDecls HscEnv
hsc_env0 [LImportDecl GhcPs]
import_decls = HscEnv -> Hsc GlobalRdrEnv -> IO GlobalRdrEnv
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc GlobalRdrEnv -> IO GlobalRdrEnv)
-> Hsc GlobalRdrEnv -> IO GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
IO ((WarningMessages, WarningMessages), Maybe GlobalRdrEnv)
-> Hsc GlobalRdrEnv
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe GlobalRdrEnv)
-> Hsc GlobalRdrEnv)
-> IO ((WarningMessages, WarningMessages), Maybe GlobalRdrEnv)
-> Hsc GlobalRdrEnv
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [LImportDecl GhcPs]
-> IO ((WarningMessages, WarningMessages), Maybe GlobalRdrEnv)
tcRnImportDecls HscEnv
hsc_env [LImportDecl GhcPs]
import_decls
hscParse :: HscEnv -> ModSummary -> IO HsParsedModule
hscParse :: HscEnv -> ModSummary -> IO HsParsedModule
hscParse HscEnv
hsc_env ModSummary
mod_summary = HscEnv -> Hsc HsParsedModule -> IO HsParsedModule
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc HsParsedModule -> IO HsParsedModule)
-> Hsc HsParsedModule -> IO HsParsedModule
forall a b. (a -> b) -> a -> b
$ ModSummary -> Hsc HsParsedModule
hscParse' ModSummary
mod_summary
hscParse' :: ModSummary -> Hsc HsParsedModule
hscParse' :: ModSummary -> Hsc HsParsedModule
hscParse' ModSummary
mod_summary
| Just HsParsedModule
r <- ModSummary -> Maybe HsParsedModule
ms_parsed_mod ModSummary
mod_summary = HsParsedModule -> Hsc HsParsedModule
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return HsParsedModule
r
| IsSafeImport
otherwise = {-# SCC "Parser" #-}
SDoc
-> (HsParsedModule -> ())
-> Hsc HsParsedModule
-> Hsc HsParsedModule
forall (m :: * -> *) a.
(MonadIO m, HasDynFlags m) =>
SDoc -> (a -> ()) -> m a -> m a
External instance of the constraint type HasDynFlags Hsc
External instance of the constraint type MonadIO Hsc
withTimingD (String -> SDoc
text String
"Parser"SDoc -> SDoc -> SDoc
<+>SDoc -> SDoc
brackets (Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr (Module -> SDoc) -> Module -> SDoc
forall a b. (a -> b) -> a -> b
$ ModSummary -> Module
ms_mod ModSummary
mod_summary))
(() -> HsParsedModule -> ()
forall a b. a -> b -> a
const ()) (Hsc HsParsedModule -> Hsc HsParsedModule)
-> Hsc HsParsedModule -> Hsc HsParsedModule
forall a b. (a -> b) -> a -> b
$ do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
let src_filename :: String
src_filename = ModSummary -> String
ms_hspp_file ModSummary
mod_summary
maybe_src_buf :: Maybe StringBuffer
maybe_src_buf = ModSummary -> Maybe StringBuffer
ms_hspp_buf ModSummary
mod_summary
StringBuffer
buf <- case Maybe StringBuffer
maybe_src_buf of
Just StringBuffer
b -> StringBuffer -> Hsc StringBuffer
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return StringBuffer
b
Maybe StringBuffer
Nothing -> IO StringBuffer -> Hsc StringBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO StringBuffer -> Hsc StringBuffer)
-> IO StringBuffer -> Hsc StringBuffer
forall a b. (a -> b) -> a -> b
$ String -> IO StringBuffer
hGetStringBuffer String
src_filename
let loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
mkFastString String
src_filename) Int
1 Int
1
let parseMod :: P (Located HsModule)
parseMod | HscSource
HsigFile HscSource -> HscSource -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq HscSource
== ModSummary -> HscSource
ms_hsc_src ModSummary
mod_summary
= P (Located HsModule)
parseSignature
| IsSafeImport
otherwise = P (Located HsModule)
parseModule
case P (Located HsModule) -> PState -> ParseResult (Located HsModule)
forall a. P a -> PState -> ParseResult a
unP P (Located HsModule)
parseMod (DynFlags -> StringBuffer -> RealSrcLoc -> PState
mkPState DynFlags
dflags StringBuffer
buf RealSrcLoc
loc) of
PFailed PState
pst ->
(WarningMessages, WarningMessages) -> Hsc HsParsedModule
forall a. (WarningMessages, WarningMessages) -> Hsc a
handleWarningsThrowErrors (PState -> DynFlags -> (WarningMessages, WarningMessages)
getMessages PState
pst DynFlags
dflags)
POk PState
pst Located HsModule
rdr_module -> do
let (WarningMessages
warns, WarningMessages
errs) = PState -> DynFlags -> (WarningMessages, WarningMessages)
getMessages PState
pst DynFlags
dflags
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_parsed String
"Parser"
DumpFormat
FormatHaskell (Located HsModule -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type Outputable HsModule
ppr Located HsModule
rdr_module)
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_parsed_ast String
"Parser AST"
DumpFormat
FormatHaskell (BlankSrcSpan -> Located HsModule -> SDoc
forall a. Data a => BlankSrcSpan -> a -> SDoc
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data HsModule
showAstData BlankSrcSpan
NoBlankSrcSpan Located HsModule
rdr_module)
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_source_stats String
"Source Statistics"
DumpFormat
FormatText (IsSafeImport -> Located HsModule -> SDoc
ppSourceStats IsSafeImport
False Located HsModule
rdr_module)
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (IsSafeImport -> IsSafeImport
not (IsSafeImport -> IsSafeImport) -> IsSafeImport -> IsSafeImport
forall a b. (a -> b) -> a -> b
$ WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag WarningMessages
errs) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ WarningMessages -> Hsc ()
forall (io :: * -> *) a. MonadIO io => WarningMessages -> io a
External instance of the constraint type MonadIO Hsc
throwErrors WarningMessages
errs
let n_hspp :: String
n_hspp = String -> String
FilePath.normalise String
src_filename
srcs0 :: [String]
srcs0 = [String] -> [String]
forall a. Eq a => [a] -> [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> IsSafeImport) -> [String] -> [String]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter (IsSafeImport -> IsSafeImport
not (IsSafeImport -> IsSafeImport)
-> (String -> IsSafeImport) -> String -> IsSafeImport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DynFlags -> String
tmpDir DynFlags
dflags String -> String -> IsSafeImport
forall a. Eq a => [a] -> [a] -> IsSafeImport
External instance of the constraint type Eq Char
`isPrefixOf`))
([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> IsSafeImport) -> [String] -> [String]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter (IsSafeImport -> IsSafeImport
not (IsSafeImport -> IsSafeImport)
-> (String -> IsSafeImport) -> String -> IsSafeImport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
== String
n_hspp))
([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
FilePath.normalise
([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> IsSafeImport) -> [String] -> [String]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter (IsSafeImport -> IsSafeImport
not (IsSafeImport -> IsSafeImport)
-> (String -> IsSafeImport) -> String -> IsSafeImport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> IsSafeImport
forall a. Eq a => [a] -> [a] -> IsSafeImport
External instance of the constraint type Eq Char
isPrefixOf String
"<")
([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (FastString -> String) -> [FastString] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map FastString -> String
unpackFS
([FastString] -> [String]) -> [FastString] -> [String]
forall a b. (a -> b) -> a -> b
$ PState -> [FastString]
srcfiles PState
pst
srcs1 :: [String]
srcs1 = case ModLocation -> Maybe String
ml_hs_file (ModSummary -> ModLocation
ms_location ModSummary
mod_summary) of
Just String
f -> (String -> IsSafeImport) -> [String] -> [String]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter (String -> String -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
/= String -> String
FilePath.normalise String
f) [String]
srcs0
Maybe String
Nothing -> [String]
srcs0
[String]
srcs2 <- IO [String] -> Hsc [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO [String] -> Hsc [String]) -> IO [String] -> Hsc [String]
forall a b. (a -> b) -> a -> b
$ (String -> IO IsSafeImport) -> [String] -> IO [String]
forall (m :: * -> *) a.
Applicative m =>
(a -> m IsSafeImport) -> [a] -> m [a]
External instance of the constraint type Applicative IO
filterM String -> IO IsSafeImport
doesFileExist [String]
srcs1
let api_anns :: ApiAnns
api_anns = ApiAnns :: Map ApiAnnKey [RealSrcSpan]
-> Maybe RealSrcSpan
-> Map RealSrcSpan [RealLocated AnnotationComment]
-> [RealLocated AnnotationComment]
-> ApiAnns
ApiAnns {
apiAnnItems :: Map ApiAnnKey [RealSrcSpan]
apiAnnItems = ([RealSrcSpan] -> [RealSrcSpan] -> [RealSrcSpan])
-> [(ApiAnnKey, [RealSrcSpan])] -> Map ApiAnnKey [RealSrcSpan]
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
External instance of the constraint type Ord RealSrcSpan
External instance of the constraint type Ord AnnKeywordId
M.fromListWith [RealSrcSpan] -> [RealSrcSpan] -> [RealSrcSpan]
forall a. [a] -> [a] -> [a]
(++) ([(ApiAnnKey, [RealSrcSpan])] -> Map ApiAnnKey [RealSrcSpan])
-> [(ApiAnnKey, [RealSrcSpan])] -> Map ApiAnnKey [RealSrcSpan]
forall a b. (a -> b) -> a -> b
$ PState -> [(ApiAnnKey, [RealSrcSpan])]
annotations PState
pst,
apiAnnEofPos :: Maybe RealSrcSpan
apiAnnEofPos = PState -> Maybe RealSrcSpan
eof_pos PState
pst,
apiAnnComments :: Map RealSrcSpan [RealLocated AnnotationComment]
apiAnnComments = [(RealSrcSpan, [RealLocated AnnotationComment])]
-> Map RealSrcSpan [RealLocated AnnotationComment]
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type Ord RealSrcSpan
M.fromList (PState -> [(RealSrcSpan, [RealLocated AnnotationComment])]
annotations_comments PState
pst),
apiAnnRogueComments :: [RealLocated AnnotationComment]
apiAnnRogueComments = PState -> [RealLocated AnnotationComment]
comment_q PState
pst
}
res :: HsParsedModule
res = HsParsedModule :: Located HsModule -> [String] -> ApiAnns -> HsParsedModule
HsParsedModule {
hpm_module :: Located HsModule
hpm_module = Located HsModule
rdr_module,
hpm_src_files :: [String]
hpm_src_files = [String]
srcs2,
hpm_annotations :: ApiAnns
hpm_annotations = ApiAnns
api_anns
}
let applyPluginAction :: Plugin -> [String] -> HsParsedModule -> Hsc HsParsedModule
applyPluginAction Plugin
p [String]
opts
= Plugin
-> [String] -> ModSummary -> HsParsedModule -> Hsc HsParsedModule
parsedResultAction Plugin
p [String]
opts ModSummary
mod_summary
DynFlags
-> (Plugin -> [String] -> HsParsedModule -> Hsc HsParsedModule)
-> HsParsedModule
-> Hsc HsParsedModule
forall (m :: * -> *) a.
Monad m =>
DynFlags -> PluginOperation m a -> a -> m a
External instance of the constraint type Monad Hsc
withPlugins DynFlags
dflags Plugin -> [String] -> HsParsedModule -> Hsc HsParsedModule
applyPluginAction HsParsedModule
res
extract_renamed_stuff :: ModSummary -> TcGblEnv -> Hsc RenamedStuff
ModSummary
mod_summary TcGblEnv
tc_result = do
let rn_info :: RenamedStuff
rn_info = TcGblEnv -> RenamedStuff
getRenamedStuff TcGblEnv
tc_result
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_rn_ast String
"Renamer"
DumpFormat
FormatHaskell (BlankSrcSpan -> RenamedStuff -> SDoc
forall a. Data a => BlankSrcSpan -> a -> SDoc
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall a b c d.
(Data a, Data b, Data c, Data d) =>
Data (a, b, c, d)
External instance of the constraint type Data (HsGroup GhcRn)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data (ImportDecl GhcRn)
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data (IE GhcRn)
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data AvailInfo
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data HsDocString
showAstData BlankSrcSpan
NoBlankSrcSpan RenamedStuff
rn_info)
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (GeneralFlag -> DynFlags -> IsSafeImport
gopt GeneralFlag
Opt_WriteHie DynFlags
dflags) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ do
HieFile
hieFile <- ModSummary
-> TcGblEnv
-> (HsGroup GhcRn, [LImportDecl GhcRn],
Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
-> Hsc HieFile
mkHieFile ModSummary
mod_summary TcGblEnv
tc_result (RenamedStuff
-> (HsGroup GhcRn, [LImportDecl GhcRn],
Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
forall a. HasCallStack => Maybe a -> a
fromJust RenamedStuff
rn_info)
let out_file :: String
out_file = ModLocation -> String
ml_hie_file (ModLocation -> String) -> ModLocation -> String
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModLocation
ms_location ModSummary
mod_summary
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ String -> HieFile -> IO ()
writeHieFile String
out_file HieFile
hieFile
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_hie String
"HIE AST" DumpFormat
FormatHaskell (HieASTs Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (HieASTs a)
External instance of the constraint type Outputable Int
ppr (HieASTs Int -> SDoc) -> HieASTs Int -> SDoc
forall a b. (a -> b) -> a -> b
$ HieFile -> HieASTs Int
hie_asts HieFile
hieFile)
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (GeneralFlag -> DynFlags -> IsSafeImport
gopt GeneralFlag
Opt_ValidateHie DynFlags
dflags) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hs_env <- (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a.
(HscEnv -> WarningMessages -> IO (a, WarningMessages)) -> Hsc a
Hsc ((HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv)
-> (HscEnv -> WarningMessages -> IO (HscEnv, WarningMessages))
-> Hsc HscEnv
forall a b. (a -> b) -> a -> b
$ \HscEnv
e WarningMessages
w -> (HscEnv, WarningMessages) -> IO (HscEnv, WarningMessages)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (HscEnv
e, WarningMessages
w)
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ do
case Module -> Map FastString (HieAST Int) -> [SDoc]
forall a. Module -> Map FastString (HieAST a) -> [SDoc]
validateScopes (HieFile -> Module
hie_module HieFile
hieFile) (Map FastString (HieAST Int) -> [SDoc])
-> Map FastString (HieAST Int) -> [SDoc]
forall a b. (a -> b) -> a -> b
$ HieASTs Int -> Map FastString (HieAST Int)
forall a. HieASTs a -> Map FastString (HieAST a)
getAsts (HieASTs Int -> Map FastString (HieAST Int))
-> HieASTs Int -> Map FastString (HieAST Int)
forall a b. (a -> b) -> a -> b
$ HieFile -> HieASTs Int
hie_asts HieFile
hieFile of
[] -> DynFlags -> SDoc -> IO ()
putMsg DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Got valid scopes"
[SDoc]
xs -> do
DynFlags -> SDoc -> IO ()
putMsg DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Got invalid scopes"
(SDoc -> IO ()) -> [SDoc] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
mapM_ (DynFlags -> SDoc -> IO ()
putMsg DynFlags
dflags) [SDoc]
xs
HieFileResult
file' <- NameCacheUpdater -> String -> IO HieFileResult
readHieFile ((forall c. (NameCache -> (NameCache, c)) -> IO c)
-> NameCacheUpdater
NCU ((forall c. (NameCache -> (NameCache, c)) -> IO c)
-> NameCacheUpdater)
-> (forall c. (NameCache -> (NameCache, c)) -> IO c)
-> NameCacheUpdater
forall a b. (a -> b) -> a -> b
$ IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
forall c. IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
updNameCache (IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c)
-> IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
forall a b. (a -> b) -> a -> b
$ HscEnv -> IORef NameCache
hsc_NC HscEnv
hs_env) String
out_file
case Diff HieFile
diffFile HieFile
hieFile (HieFileResult -> HieFile
hie_file_result HieFileResult
file') of
[] ->
DynFlags -> SDoc -> IO ()
putMsg DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Got no roundtrip errors"
[SDoc]
xs -> do
DynFlags -> SDoc -> IO ()
putMsg DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Got roundtrip errors"
(SDoc -> IO ()) -> [SDoc] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
mapM_ (DynFlags -> SDoc -> IO ()
putMsg (DynFlags -> DumpFlag -> DynFlags
dopt_set DynFlags
dflags DumpFlag
Opt_D_ppr_debug)) [SDoc]
xs
RenamedStuff -> Hsc RenamedStuff
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return RenamedStuff
rn_info
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule
-> IO (TcGblEnv, RenamedStuff)
hscTypecheckRename :: HscEnv
-> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff)
hscTypecheckRename HscEnv
hsc_env ModSummary
mod_summary HsParsedModule
rdr_module = HscEnv
-> Hsc (TcGblEnv, RenamedStuff) -> IO (TcGblEnv, RenamedStuff)
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc (TcGblEnv, RenamedStuff) -> IO (TcGblEnv, RenamedStuff))
-> Hsc (TcGblEnv, RenamedStuff) -> IO (TcGblEnv, RenamedStuff)
forall a b. (a -> b) -> a -> b
$
IsSafeImport
-> ModSummary
-> Maybe HsParsedModule
-> Hsc (TcGblEnv, RenamedStuff)
hsc_typecheck IsSafeImport
True ModSummary
mod_summary (HsParsedModule -> Maybe HsParsedModule
forall a. a -> Maybe a
Just HsParsedModule
rdr_module)
hsc_typecheck :: Bool
-> ModSummary -> Maybe HsParsedModule
-> Hsc (TcGblEnv, RenamedStuff)
hsc_typecheck :: IsSafeImport
-> ModSummary
-> Maybe HsParsedModule
-> Hsc (TcGblEnv, RenamedStuff)
hsc_typecheck IsSafeImport
keep_rn ModSummary
mod_summary Maybe HsParsedModule
mb_rdr_module = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
let hsc_src :: HscSource
hsc_src = ModSummary -> HscSource
ms_hsc_src ModSummary
mod_summary
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
outer_mod :: Module
outer_mod = ModSummary -> Module
ms_mod ModSummary
mod_summary
mod_name :: ModuleName
mod_name = Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
outer_mod
outer_mod' :: Module
outer_mod' = Unit -> ModuleName -> Module
forall u. u -> ModuleName -> GenModule u
mkModule (DynFlags -> Unit
thisPackage DynFlags
dflags) ModuleName
mod_name
inner_mod :: Module
inner_mod = DynFlags -> ModuleName -> Module
canonicalizeHomeModule DynFlags
dflags ModuleName
mod_name
src_filename :: String
src_filename = ModSummary -> String
ms_hspp_file ModSummary
mod_summary
real_loc :: RealSrcSpan
real_loc = RealSrcLoc -> RealSrcSpan
realSrcLocSpan (RealSrcLoc -> RealSrcSpan) -> RealSrcLoc -> RealSrcSpan
forall a b. (a -> b) -> a -> b
$ FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
mkFastString String
src_filename) Int
1 Int
1
keep_rn' :: IsSafeImport
keep_rn' = GeneralFlag -> DynFlags -> IsSafeImport
gopt GeneralFlag
Opt_WriteHie DynFlags
dflags IsSafeImport -> IsSafeImport -> IsSafeImport
|| IsSafeImport
keep_rn
MASSERT( moduleUnit outer_mod == thisPackage dflags )
TcGblEnv
tc_result <- if HscSource
hsc_src HscSource -> HscSource -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq HscSource
== HscSource
HsigFile IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport -> IsSafeImport
not (Module -> IsSafeImport
forall u. GenModule (GenUnit u) -> IsSafeImport
isHoleModule Module
inner_mod)
then IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv)
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Module
-> RealSrcSpan
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
tcRnInstantiateSignature HscEnv
hsc_env Module
outer_mod' RealSrcSpan
real_loc
else
do HsParsedModule
hpm <- case Maybe HsParsedModule
mb_rdr_module of
Just HsParsedModule
hpm -> HsParsedModule -> Hsc HsParsedModule
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return HsParsedModule
hpm
Maybe HsParsedModule
Nothing -> ModSummary -> Hsc HsParsedModule
hscParse' ModSummary
mod_summary
TcGblEnv
tc_result0 <- ModSummary -> IsSafeImport -> HsParsedModule -> Hsc TcGblEnv
tcRnModule' ModSummary
mod_summary IsSafeImport
keep_rn' HsParsedModule
hpm
if HscSource
hsc_src HscSource -> HscSource -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq HscSource
== HscSource
HsigFile
then do (ModIface
iface, Maybe Fingerprint
_, ModDetails
_) <- IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails))
-> IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> TcGblEnv
-> Maybe Fingerprint
-> IO (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface HscEnv
hsc_env TcGblEnv
tc_result0 Maybe Fingerprint
forall a. Maybe a
Nothing
IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv)
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$
HscEnv
-> HsParsedModule
-> TcGblEnv
-> ModIface
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
tcRnMergeSignatures HscEnv
hsc_env HsParsedModule
hpm TcGblEnv
tc_result0 ModIface
iface
else TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tc_result0
RenamedStuff
rn_info <- ModSummary -> TcGblEnv -> Hsc RenamedStuff
extract_renamed_stuff ModSummary
mod_summary TcGblEnv
tc_result
(TcGblEnv, RenamedStuff) -> Hsc (TcGblEnv, RenamedStuff)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (TcGblEnv
tc_result, RenamedStuff
rn_info)
tcRnModule' :: ModSummary -> Bool -> HsParsedModule
-> Hsc TcGblEnv
tcRnModule' :: ModSummary -> IsSafeImport -> HsParsedModule -> Hsc TcGblEnv
tcRnModule' ModSummary
sum IsSafeImport
save_rn_syntax HsParsedModule
mod = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (IsSafeImport -> IsSafeImport
not (DynFlags -> IsSafeImport
safeHaskellModeEnabled DynFlags
dflags)
IsSafeImport -> IsSafeImport -> IsSafeImport
&& WarningFlag -> DynFlags -> IsSafeImport
wopt WarningFlag
Opt_WarnMissingSafeHaskellMode DynFlags
dflags) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$
WarningMessages -> Hsc ()
logWarnings (WarningMessages -> Hsc ()) -> WarningMessages -> Hsc ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$
WarnReason -> ErrMsg -> ErrMsg
makeIntoWarning (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnMissingSafeHaskellMode) (ErrMsg -> ErrMsg) -> ErrMsg -> ErrMsg
forall a b. (a -> b) -> a -> b
$
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags (Located HsModule -> SrcSpan
forall l e. GenLocated l e -> l
getLoc (HsParsedModule -> Located HsModule
hpm_module HsParsedModule
mod)) (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
SDoc
warnMissingSafeHaskellMode
TcGblEnv
tcg_res <- {-# SCC "Typecheck-Rename" #-}
IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv)
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$
HscEnv
-> ModSummary
-> IsSafeImport
-> HsParsedModule
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
tcRnModule HscEnv
hsc_env ModSummary
sum
IsSafeImport
save_rn_syntax HsParsedModule
mod
(IsSafeImport
tcSafeOK, WarningMessages
whyUnsafe) <- IO (IsSafeImport, WarningMessages)
-> Hsc (IsSafeImport, WarningMessages)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (IsSafeImport, WarningMessages)
-> Hsc (IsSafeImport, WarningMessages))
-> IO (IsSafeImport, WarningMessages)
-> Hsc (IsSafeImport, WarningMessages)
forall a b. (a -> b) -> a -> b
$ IORef (IsSafeImport, WarningMessages)
-> IO (IsSafeImport, WarningMessages)
forall a. IORef a -> IO a
readIORef (TcGblEnv -> IORef (IsSafeImport, WarningMessages)
tcg_safeInfer TcGblEnv
tcg_res)
let allSafeOK :: IsSafeImport
allSafeOK = DynFlags -> IsSafeImport
safeInferred DynFlags
dflags IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport
tcSafeOK
if IsSafeImport -> IsSafeImport
not (DynFlags -> IsSafeImport
safeHaskellOn DynFlags
dflags)
IsSafeImport -> IsSafeImport -> IsSafeImport
|| (DynFlags -> IsSafeImport
safeInferOn DynFlags
dflags IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport -> IsSafeImport
not IsSafeImport
allSafeOK)
then TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer TcGblEnv
tcg_res WarningMessages
whyUnsafe
else do
TcGblEnv
tcg_res' <- TcGblEnv -> Hsc TcGblEnv
hscCheckSafeImports TcGblEnv
tcg_res
IsSafeImport
safe <- IO IsSafeImport -> Hsc IsSafeImport
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO IsSafeImport -> Hsc IsSafeImport)
-> IO IsSafeImport -> Hsc IsSafeImport
forall a b. (a -> b) -> a -> b
$ (IsSafeImport, WarningMessages) -> IsSafeImport
forall a b. (a, b) -> a
fst ((IsSafeImport, WarningMessages) -> IsSafeImport)
-> IO (IsSafeImport, WarningMessages) -> IO IsSafeImport
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> IORef (IsSafeImport, WarningMessages)
-> IO (IsSafeImport, WarningMessages)
forall a. IORef a -> IO a
readIORef (TcGblEnv -> IORef (IsSafeImport, WarningMessages)
tcg_safeInfer TcGblEnv
tcg_res')
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when IsSafeImport
safe (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ do
case WarningFlag -> DynFlags -> IsSafeImport
wopt WarningFlag
Opt_WarnSafe DynFlags
dflags of
IsSafeImport
True
| DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags SafeHaskellMode -> SafeHaskellMode -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
== SafeHaskellMode
Sf_Safe -> () -> Hsc ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ()
| IsSafeImport
otherwise -> (WarningMessages -> Hsc ()
logWarnings (WarningMessages -> Hsc ()) -> WarningMessages -> Hsc ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$
WarnReason -> ErrMsg -> ErrMsg
makeIntoWarning (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnSafe) (ErrMsg -> ErrMsg) -> ErrMsg -> ErrMsg
forall a b. (a -> b) -> a -> b
$
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags (DynFlags -> SrcSpan
warnSafeOnLoc DynFlags
dflags) (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
TcGblEnv -> SDoc
errSafe TcGblEnv
tcg_res')
IsSafeImport
False | DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags SafeHaskellMode -> SafeHaskellMode -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
== SafeHaskellMode
Sf_Trustworthy IsSafeImport -> IsSafeImport -> IsSafeImport
&&
WarningFlag -> DynFlags -> IsSafeImport
wopt WarningFlag
Opt_WarnTrustworthySafe DynFlags
dflags ->
(WarningMessages -> Hsc ()
logWarnings (WarningMessages -> Hsc ()) -> WarningMessages -> Hsc ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$
WarnReason -> ErrMsg -> ErrMsg
makeIntoWarning (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnTrustworthySafe) (ErrMsg -> ErrMsg) -> ErrMsg -> ErrMsg
forall a b. (a -> b) -> a -> b
$
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags (DynFlags -> SrcSpan
trustworthyOnLoc DynFlags
dflags) (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
TcGblEnv -> SDoc
errTwthySafe TcGblEnv
tcg_res')
IsSafeImport
False -> () -> Hsc ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ()
TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_res'
where
pprMod :: TcGblEnv -> SDoc
pprMod TcGblEnv
t = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (ModuleName -> SDoc) -> ModuleName -> SDoc
forall a b. (a -> b) -> a -> b
$ Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (Module -> ModuleName) -> Module -> ModuleName
forall a b. (a -> b) -> a -> b
$ TcGblEnv -> Module
tcg_mod TcGblEnv
t
errSafe :: TcGblEnv -> SDoc
errSafe TcGblEnv
t = SDoc -> SDoc
quotes (TcGblEnv -> SDoc
pprMod TcGblEnv
t) SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"has been inferred as safe!"
errTwthySafe :: TcGblEnv -> SDoc
errTwthySafe TcGblEnv
t = SDoc -> SDoc
quotes (TcGblEnv -> SDoc
pprMod TcGblEnv
t)
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is marked as Trustworthy but has been inferred as safe!"
warnMissingSafeHaskellMode :: SDoc
warnMissingSafeHaskellMode = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (ModSummary -> Module
ms_mod ModSummary
sum))
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is missing Safe Haskell mode"
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
hscDesugar HscEnv
hsc_env ModSummary
mod_summary TcGblEnv
tc_result =
HscEnv -> Hsc ModGuts -> IO ModGuts
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc ModGuts -> IO ModGuts) -> Hsc ModGuts -> IO ModGuts
forall a b. (a -> b) -> a -> b
$ ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' (ModSummary -> ModLocation
ms_location ModSummary
mod_summary) TcGblEnv
tc_result
hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' :: ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' ModLocation
mod_location TcGblEnv
tc_result = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
ModGuts
r <- IO ((WarningMessages, WarningMessages), Maybe ModGuts)
-> Hsc ModGuts
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe ModGuts)
-> Hsc ModGuts)
-> IO ((WarningMessages, WarningMessages), Maybe ModGuts)
-> Hsc ModGuts
forall a b. (a -> b) -> a -> b
$
{-# SCC "deSugar" #-}
HscEnv
-> ModLocation
-> TcGblEnv
-> IO ((WarningMessages, WarningMessages), Maybe ModGuts)
deSugar HscEnv
hsc_env ModLocation
mod_location TcGblEnv
tc_result
Hsc ()
handleWarnings
ModGuts -> Hsc ModGuts
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ModGuts
r
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails HscEnv
hsc_env TcGblEnv
tc_result = HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc HscEnv
hsc_env TcGblEnv
tc_result
type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModSummary -> IO ()
hscIncrementalFrontend :: Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int,Int)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
hscIncrementalFrontend :: IsSafeImport
-> Maybe TcGblEnv
-> Maybe Messager
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int, Int)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
hscIncrementalFrontend
IsSafeImport
always_do_basic_recompilation_check Maybe TcGblEnv
m_tc_result
Maybe Messager
mHscMessage ModSummary
mod_summary SourceModified
source_modified Maybe ModIface
mb_old_iface (Int, Int)
mod_index
= do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
let msg :: RecompileRequired -> IO ()
msg RecompileRequired
what = case Maybe Messager
mHscMessage of
Just Messager
hscMessage -> Messager
hscMessage HscEnv
hsc_env (Int, Int)
mod_index RecompileRequired
what ModSummary
mod_summary
Maybe Messager
Nothing -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
skip :: a -> m (Either a b)
skip a
iface = do
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RecompileRequired -> IO ()
msg RecompileRequired
UpToDate
Either a b -> m (Either a b)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
return (Either a b -> m (Either a b)) -> Either a b -> m (Either a b)
forall a b. (a -> b) -> a -> b
$ a -> Either a b
forall a b. a -> Either a b
Left a
iface
compile :: b -> RecompileRequired -> Hsc (Either a (FrontendResult, b))
compile b
mb_old_hash RecompileRequired
reason = do
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ RecompileRequired -> IO ()
msg RecompileRequired
reason
(TcGblEnv
tc_result, RenamedStuff
_) <- IsSafeImport
-> ModSummary
-> Maybe HsParsedModule
-> Hsc (TcGblEnv, RenamedStuff)
hsc_typecheck IsSafeImport
False ModSummary
mod_summary Maybe HsParsedModule
forall a. Maybe a
Nothing
Either a (FrontendResult, b) -> Hsc (Either a (FrontendResult, b))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Either a (FrontendResult, b)
-> Hsc (Either a (FrontendResult, b)))
-> Either a (FrontendResult, b)
-> Hsc (Either a (FrontendResult, b))
forall a b. (a -> b) -> a -> b
$ (FrontendResult, b) -> Either a (FrontendResult, b)
forall a b. b -> Either a b
Right (TcGblEnv -> FrontendResult
FrontendTypecheck TcGblEnv
tc_result, b
mb_old_hash)
stable :: IsSafeImport
stable = case SourceModified
source_modified of
SourceModified
SourceUnmodifiedAndStable -> IsSafeImport
True
SourceModified
_ -> IsSafeImport
False
case Maybe TcGblEnv
m_tc_result of
Just TcGblEnv
tc_result
| IsSafeImport -> IsSafeImport
not IsSafeImport
always_do_basic_recompilation_check ->
Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint)))
-> Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall a b. (a -> b) -> a -> b
$ (FrontendResult, Maybe Fingerprint)
-> Either ModIface (FrontendResult, Maybe Fingerprint)
forall a b. b -> Either a b
Right (TcGblEnv -> FrontendResult
FrontendTypecheck TcGblEnv
tc_result, Maybe Fingerprint
forall a. Maybe a
Nothing)
Maybe TcGblEnv
_ -> do
(RecompileRequired
recomp_reqd, Maybe ModIface
mb_checked_iface)
<- {-# SCC "checkOldIface" #-}
IO (RecompileRequired, Maybe ModIface)
-> Hsc (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (RecompileRequired, Maybe ModIface)
-> Hsc (RecompileRequired, Maybe ModIface))
-> IO (RecompileRequired, Maybe ModIface)
-> Hsc (RecompileRequired, Maybe ModIface)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IO (RecompileRequired, Maybe ModIface)
checkOldIface HscEnv
hsc_env ModSummary
mod_summary
SourceModified
source_modified Maybe ModIface
mb_old_iface
let mb_old_hash :: Maybe Fingerprint
mb_old_hash = (ModIface -> Fingerprint) -> Maybe ModIface -> Maybe Fingerprint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap (ModIfaceBackend -> Fingerprint
mi_iface_hash (ModIfaceBackend -> Fingerprint)
-> (ModIface -> ModIfaceBackend) -> ModIface -> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface -> ModIfaceBackend
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts) Maybe ModIface
mb_checked_iface
case Maybe ModIface
mb_checked_iface of
Just ModIface
iface | IsSafeImport -> IsSafeImport
not (RecompileRequired -> IsSafeImport
recompileRequired RecompileRequired
recomp_reqd) ->
case Maybe TcGblEnv
m_tc_result of
Maybe TcGblEnv
Nothing
| ModIface -> IsSafeImport
forall (phase :: ModIfacePhase). ModIface_ phase -> IsSafeImport
mi_used_th ModIface
iface IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport -> IsSafeImport
not IsSafeImport
stable ->
Maybe Fingerprint
-> RecompileRequired
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall {b} {a}.
b -> RecompileRequired -> Hsc (Either a (FrontendResult, b))
compile Maybe Fingerprint
mb_old_hash (String -> RecompileRequired
RecompBecause String
"TH")
Maybe TcGblEnv
_ ->
ModIface
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall {m :: * -> *} {a} {b}. MonadIO m => a -> m (Either a b)
External instance of the constraint type MonadIO Hsc
skip ModIface
iface
Maybe ModIface
_ ->
case Maybe TcGblEnv
m_tc_result of
Maybe TcGblEnv
Nothing -> Maybe Fingerprint
-> RecompileRequired
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall {b} {a}.
b -> RecompileRequired -> Hsc (Either a (FrontendResult, b))
compile Maybe Fingerprint
mb_old_hash RecompileRequired
recomp_reqd
Just TcGblEnv
tc_result ->
Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint)))
-> Either ModIface (FrontendResult, Maybe Fingerprint)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
forall a b. (a -> b) -> a -> b
$ (FrontendResult, Maybe Fingerprint)
-> Either ModIface (FrontendResult, Maybe Fingerprint)
forall a b. b -> Either a b
Right (TcGblEnv -> FrontendResult
FrontendTypecheck TcGblEnv
tc_result, Maybe Fingerprint
mb_old_hash)
hscIncrementalCompile :: Bool
-> Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int,Int)
-> IO (HscStatus, DynFlags)
hscIncrementalCompile :: IsSafeImport
-> Maybe TcGblEnv
-> Maybe Messager
-> HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int, Int)
-> IO (HscStatus, DynFlags)
hscIncrementalCompile IsSafeImport
always_do_basic_recompilation_check Maybe TcGblEnv
m_tc_result
Maybe Messager
mHscMessage HscEnv
hsc_env' ModSummary
mod_summary SourceModified
source_modified Maybe ModIface
mb_old_iface (Int, Int)
mod_index
= do
DynFlags
dflags <- HscEnv -> DynFlags -> IO DynFlags
initializePlugins HscEnv
hsc_env' (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env')
let hsc_env'' :: HscEnv
hsc_env'' = HscEnv
hsc_env' { hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags }
IORef TypeEnv
type_env_var <- TypeEnv -> IO (IORef TypeEnv)
forall a. a -> IO (IORef a)
newIORef TypeEnv
forall a. NameEnv a
emptyNameEnv
let mod :: Module
mod = ModSummary -> Module
ms_mod ModSummary
mod_summary
hsc_env :: HscEnv
hsc_env | GhcMode -> IsSafeImport
isOneShot (DynFlags -> GhcMode
ghcMode (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env''))
= HscEnv
hsc_env'' { hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
hsc_type_env_var = (Module, IORef TypeEnv) -> Maybe (Module, IORef TypeEnv)
forall a. a -> Maybe a
Just (Module
mod, IORef TypeEnv
type_env_var) }
| IsSafeImport
otherwise
= HscEnv
hsc_env''
HscEnv -> Hsc (HscStatus, DynFlags) -> IO (HscStatus, DynFlags)
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc (HscStatus, DynFlags) -> IO (HscStatus, DynFlags))
-> Hsc (HscStatus, DynFlags) -> IO (HscStatus, DynFlags)
forall a b. (a -> b) -> a -> b
$ do
Either ModIface (FrontendResult, Maybe Fingerprint)
e <- IsSafeImport
-> Maybe TcGblEnv
-> Maybe Messager
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> (Int, Int)
-> Hsc (Either ModIface (FrontendResult, Maybe Fingerprint))
hscIncrementalFrontend IsSafeImport
always_do_basic_recompilation_check Maybe TcGblEnv
m_tc_result Maybe Messager
mHscMessage
ModSummary
mod_summary SourceModified
source_modified Maybe ModIface
mb_old_iface (Int, Int)
mod_index
case Either ModIface (FrontendResult, Maybe Fingerprint)
e of
Left ModIface
iface -> do
ModDetails
details <- IO ModDetails -> Hsc ModDetails
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ModDetails -> Hsc ModDetails)
-> ((ModDetails -> IO ModDetails) -> IO ModDetails)
-> (ModDetails -> IO ModDetails)
-> Hsc ModDetails
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModDetails -> IO ModDetails) -> IO ModDetails
forall a. (a -> IO a) -> IO a
fixIO ((ModDetails -> IO ModDetails) -> Hsc ModDetails)
-> (ModDetails -> IO ModDetails) -> Hsc ModDetails
forall a b. (a -> b) -> a -> b
$ \ModDetails
details' -> do
let hsc_env' :: HscEnv
hsc_env' =
HscEnv
hsc_env {
hsc_HPT :: HomePackageTable
hsc_HPT = HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
addToHpt (HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env)
(ModSummary -> ModuleName
ms_mod_name ModSummary
mod_summary) (ModIface -> ModDetails -> Maybe Linkable -> HomeModInfo
HomeModInfo ModIface
iface ModDetails
details' Maybe Linkable
forall a. Maybe a
Nothing)
}
ModDetails
details <- HscEnv -> ModIface -> IO ModDetails
genModDetails HscEnv
hsc_env' ModIface
iface
ModDetails -> IO ModDetails
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ModDetails
details
(HscStatus, DynFlags) -> Hsc (HscStatus, DynFlags)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (ModIface -> ModDetails -> HscStatus
HscUpToDate ModIface
iface ModDetails
details, DynFlags
dflags)
Right (FrontendTypecheck TcGblEnv
tc_result, Maybe Fingerprint
mb_old_hash) -> do
HscStatus
status <- ModSummary -> TcGblEnv -> Maybe Fingerprint -> Hsc HscStatus
finish ModSummary
mod_summary TcGblEnv
tc_result Maybe Fingerprint
mb_old_hash
(HscStatus, DynFlags) -> Hsc (HscStatus, DynFlags)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (HscStatus
status, DynFlags
dflags)
finish :: ModSummary
-> TcGblEnv
-> Maybe Fingerprint
-> Hsc HscStatus
finish :: ModSummary -> TcGblEnv -> Maybe Fingerprint -> Hsc HscStatus
finish ModSummary
summary TcGblEnv
tc_result Maybe Fingerprint
mb_old_hash = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
target :: HscTarget
target = DynFlags -> HscTarget
hscTarget DynFlags
dflags
hsc_src :: HscSource
hsc_src = ModSummary -> HscSource
ms_hsc_src ModSummary
summary
Maybe ModGuts
mb_desugar <-
if ModSummary -> Module
ms_mod ModSummary
summary Module -> Module -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
External instance of the constraint type Eq Unit
/= Module
gHC_PRIM IsSafeImport -> IsSafeImport -> IsSafeImport
&& HscSource
hsc_src HscSource -> HscSource -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq HscSource
== HscSource
HsSrcFile
then ModGuts -> Maybe ModGuts
forall a. a -> Maybe a
Just (ModGuts -> Maybe ModGuts) -> Hsc ModGuts -> Hsc (Maybe ModGuts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
<$> ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' (ModSummary -> ModLocation
ms_location ModSummary
summary) TcGblEnv
tc_result
else Maybe ModGuts -> Hsc (Maybe ModGuts)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative Hsc
pure Maybe ModGuts
forall a. Maybe a
Nothing
case Maybe ModGuts
mb_desugar of
Just ModGuts
desugared_guts | HscTarget
target HscTarget -> HscTarget -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq HscTarget
/= HscTarget
HscNothing -> do
[String]
plugins <- IO [String] -> Hsc [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO [String] -> Hsc [String]) -> IO [String] -> Hsc [String]
forall a b. (a -> b) -> a -> b
$ IORef [String] -> IO [String]
forall a. IORef a -> IO a
readIORef (TcGblEnv -> IORef [String]
tcg_th_coreplugins TcGblEnv
tc_result)
ModGuts
simplified_guts <- [String] -> ModGuts -> Hsc ModGuts
hscSimplify' [String]
plugins ModGuts
desugared_guts
(CgGuts
cg_guts, ModDetails
details) <- {-# SCC "CoreTidy" #-}
IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails))
-> IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails)
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram HscEnv
hsc_env ModGuts
simplified_guts
let !partial_iface :: PartialModIface
partial_iface =
{-# SCC "GHC.Driver.Main.mkPartialIface" #-}
PartialModIface -> PartialModIface
forall a. NFData a => a -> a
External instance of the constraint type forall (phase :: ModIfacePhase).
(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) =>
NFData (ModIface_ phase)
External instance of the constraint type NFData ()
External instance of the constraint type NFData IfaceDecl
force (HscEnv -> ModDetails -> ModGuts -> PartialModIface
mkPartialIface HscEnv
hsc_env ModDetails
details ModGuts
simplified_guts)
HscStatus -> Hsc HscStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return HscRecomp :: CgGuts
-> ModLocation
-> ModDetails
-> PartialModIface
-> Maybe Fingerprint
-> DynFlags
-> HscStatus
HscRecomp { hscs_guts :: CgGuts
hscs_guts = CgGuts
cg_guts,
hscs_mod_location :: ModLocation
hscs_mod_location = ModSummary -> ModLocation
ms_location ModSummary
summary,
hscs_mod_details :: ModDetails
hscs_mod_details = ModDetails
details,
hscs_partial_iface :: PartialModIface
hscs_partial_iface = PartialModIface
partial_iface,
hscs_old_iface_hash :: Maybe Fingerprint
hscs_old_iface_hash = Maybe Fingerprint
mb_old_hash,
hscs_iface_dflags :: DynFlags
hscs_iface_dflags = DynFlags
dflags }
Maybe ModGuts
_ -> do
(ModIface
iface, Maybe Fingerprint
mb_old_iface_hash, ModDetails
details) <- IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails))
-> IO (ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
forall a b. (a -> b) -> a -> b
$
HscEnv
-> TcGblEnv
-> Maybe Fingerprint
-> IO (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface HscEnv
hsc_env TcGblEnv
tc_result Maybe Fingerprint
mb_old_hash
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> ModIface -> Maybe Fingerprint -> ModLocation -> IO ()
hscMaybeWriteIface DynFlags
dflags ModIface
iface Maybe Fingerprint
mb_old_iface_hash (ModSummary -> ModLocation
ms_location ModSummary
summary)
HscStatus -> Hsc HscStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (HscStatus -> Hsc HscStatus) -> HscStatus -> Hsc HscStatus
forall a b. (a -> b) -> a -> b
$ case (HscTarget
target, HscSource
hsc_src) of
(HscTarget
HscNothing, HscSource
_) -> ModIface -> ModDetails -> HscStatus
HscNotGeneratingCode ModIface
iface ModDetails
details
(HscTarget
_, HscSource
HsBootFile) -> ModIface -> ModDetails -> HscStatus
HscUpdateBoot ModIface
iface ModDetails
details
(HscTarget
_, HscSource
HsigFile) -> ModIface -> ModDetails -> HscStatus
HscUpdateSig ModIface
iface ModDetails
details
(HscTarget, HscSource)
_ -> String -> HscStatus
forall a. String -> a
panic String
"finish"
hscMaybeWriteIface :: DynFlags -> ModIface -> Maybe Fingerprint -> ModLocation -> IO ()
hscMaybeWriteIface :: DynFlags -> ModIface -> Maybe Fingerprint -> ModLocation -> IO ()
hscMaybeWriteIface DynFlags
dflags ModIface
iface Maybe Fingerprint
old_iface ModLocation
location = do
let force_write_interface :: IsSafeImport
force_write_interface = GeneralFlag -> DynFlags -> IsSafeImport
gopt GeneralFlag
Opt_WriteInterface DynFlags
dflags
write_interface :: IsSafeImport
write_interface = case DynFlags -> HscTarget
hscTarget DynFlags
dflags of
HscTarget
HscNothing -> IsSafeImport
False
HscTarget
HscInterpreted -> IsSafeImport
False
HscTarget
_ -> IsSafeImport
True
no_change :: IsSafeImport
no_change = Maybe Fingerprint
old_iface Maybe Fingerprint -> Maybe Fingerprint -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Fingerprint
== Fingerprint -> Maybe Fingerprint
forall a. a -> Maybe a
Just (ModIfaceBackend -> Fingerprint
mi_iface_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
when (IsSafeImport
write_interface IsSafeImport -> IsSafeImport -> IsSafeImport
|| IsSafeImport
force_write_interface) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> ModIface -> IsSafeImport -> ModLocation -> IO ()
hscWriteIface DynFlags
dflags ModIface
iface IsSafeImport
no_change ModLocation
location
genModDetails :: HscEnv -> ModIface -> IO ModDetails
genModDetails :: HscEnv -> ModIface -> IO ModDetails
genModDetails HscEnv
hsc_env ModIface
old_iface
= do
ModDetails
new_details <- {-# SCC "tcRnIface" #-}
HscEnv -> IfG ModDetails -> IO ModDetails
forall a. HscEnv -> IfG a -> IO a
initIfaceLoad HscEnv
hsc_env (ModIface -> IfG ModDetails
typecheckIface ModIface
old_iface)
HscEnv -> IO ()
dumpIfaceStats HscEnv
hsc_env
ModDetails -> IO ModDetails
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ModDetails
new_details
oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
oneShotMsg :: HscEnv -> RecompileRequired -> IO ()
oneShotMsg HscEnv
hsc_env RecompileRequired
recomp =
case RecompileRequired
recomp of
RecompileRequired
UpToDate ->
DynFlags -> String -> IO ()
compilationProgressMsg (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"compilation IS NOT required"
RecompileRequired
_ ->
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
batchMsg :: Messager
batchMsg :: Messager
batchMsg HscEnv
hsc_env (Int, Int)
mod_index RecompileRequired
recomp ModSummary
mod_summary =
case RecompileRequired
recomp of
RecompileRequired
MustCompile -> String -> String -> IO ()
showMsg String
"Compiling " String
""
RecompileRequired
UpToDate
| DynFlags -> Int
verbosity (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) Int -> Int -> IsSafeImport
forall a. Ord a => a -> a -> IsSafeImport
External instance of the constraint type Ord Int
>= Int
2 -> String -> String -> IO ()
showMsg String
"Skipping " String
""
| IsSafeImport
otherwise -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
RecompBecause String
reason -> String -> String -> IO ()
showMsg String
"Compiling " (String
" [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
reason String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]")
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
showMsg :: String -> String -> IO ()
showMsg String
msg String
reason =
DynFlags -> String -> IO ()
compilationProgressMsg DynFlags
dflags (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
((Int, Int) -> String
showModuleIndex (Int, Int)
mod_index String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
msg String -> String -> String
forall a. [a] -> [a] -> [a]
++ DynFlags -> HscTarget -> IsSafeImport -> ModSummary -> String
showModMsg DynFlags
dflags (DynFlags -> HscTarget
hscTarget DynFlags
dflags)
(RecompileRequired -> IsSafeImport
recompileRequired RecompileRequired
recomp) ModSummary
mod_summary)
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
reason
hscCheckSafeImports :: TcGblEnv -> Hsc TcGblEnv
hscCheckSafeImports :: TcGblEnv -> Hsc TcGblEnv
hscCheckSafeImports TcGblEnv
tcg_env = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
TcGblEnv
tcg_env' <- TcGblEnv -> Hsc TcGblEnv
checkSafeImports TcGblEnv
tcg_env
DynFlags -> TcGblEnv -> Hsc TcGblEnv
checkRULES DynFlags
dflags TcGblEnv
tcg_env'
where
checkRULES :: DynFlags -> TcGblEnv -> Hsc TcGblEnv
checkRULES DynFlags
dflags TcGblEnv
tcg_env' = do
case DynFlags -> IsSafeImport
safeLanguageOn DynFlags
dflags of
IsSafeImport
True -> do
WarningMessages -> Hsc ()
logWarnings (WarningMessages -> Hsc ()) -> WarningMessages -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags
-> [GenLocated SrcSpan (RuleDecl GhcTc)] -> WarningMessages
warns DynFlags
dflags (TcGblEnv -> [GenLocated SrcSpan (RuleDecl GhcTc)]
tcg_rules TcGblEnv
tcg_env')
TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_env' { tcg_rules :: [GenLocated SrcSpan (RuleDecl GhcTc)]
tcg_rules = [] }
IsSafeImport
False
| DynFlags -> IsSafeImport
safeInferOn DynFlags
dflags IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport -> IsSafeImport
not ([GenLocated SrcSpan (RuleDecl GhcTc)] -> IsSafeImport
forall (t :: * -> *) a. Foldable t => t a -> IsSafeImport
External instance of the constraint type Foldable []
null ([GenLocated SrcSpan (RuleDecl GhcTc)] -> IsSafeImport)
-> [GenLocated SrcSpan (RuleDecl GhcTc)] -> IsSafeImport
forall a b. (a -> b) -> a -> b
$ TcGblEnv -> [GenLocated SrcSpan (RuleDecl GhcTc)]
tcg_rules TcGblEnv
tcg_env')
-> TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer TcGblEnv
tcg_env' (WarningMessages -> Hsc TcGblEnv)
-> WarningMessages -> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$ DynFlags
-> [GenLocated SrcSpan (RuleDecl GhcTc)] -> WarningMessages
warns DynFlags
dflags (TcGblEnv -> [GenLocated SrcSpan (RuleDecl GhcTc)]
tcg_rules TcGblEnv
tcg_env')
| IsSafeImport
otherwise
-> TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_env'
warns :: DynFlags
-> [GenLocated SrcSpan (RuleDecl GhcTc)] -> WarningMessages
warns DynFlags
dflags [GenLocated SrcSpan (RuleDecl GhcTc)]
rules = [ErrMsg] -> WarningMessages
forall a. [a] -> Bag a
listToBag ([ErrMsg] -> WarningMessages) -> [ErrMsg] -> WarningMessages
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpan (RuleDecl GhcTc) -> ErrMsg)
-> [GenLocated SrcSpan (RuleDecl GhcTc)] -> [ErrMsg]
forall a b. (a -> b) -> [a] -> [b]
map (DynFlags -> GenLocated SrcSpan (RuleDecl GhcTc) -> ErrMsg
warnRules DynFlags
dflags) [GenLocated SrcSpan (RuleDecl GhcTc)]
rules
warnRules :: DynFlags -> GenLocated SrcSpan (RuleDecl GhcTc) -> ErrMsg
warnRules :: DynFlags -> GenLocated SrcSpan (RuleDecl GhcTc) -> ErrMsg
warnRules DynFlags
dflags (L SrcSpan
loc (HsRule { rd_name :: forall pass. RuleDecl pass -> Located (SourceText, FastString)
rd_name = Located (SourceText, FastString)
n })) =
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags SrcSpan
loc (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"Rule \"" SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext ((SourceText, FastString) -> FastString
forall a b. (a, b) -> b
snd ((SourceText, FastString) -> FastString)
-> (SourceText, FastString) -> FastString
forall a b. (a -> b) -> a -> b
$ Located (SourceText, FastString) -> (SourceText, FastString)
forall l e. GenLocated l e -> e
unLoc Located (SourceText, FastString)
n) SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"\" ignored" SDoc -> SDoc -> SDoc
$+$
String -> SDoc
text String
"User defined rules are disabled under Safe Haskell"
checkSafeImports :: TcGblEnv -> Hsc TcGblEnv
checkSafeImports :: TcGblEnv -> Hsc TcGblEnv
checkSafeImports TcGblEnv
tcg_env
= do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
[(Module, SrcSpan, IsSafeImport)]
imps <- ((Module, [ImportedModsVal])
-> Hsc (Module, SrcSpan, IsSafeImport))
-> [(Module, [ImportedModsVal])]
-> Hsc [(Module, SrcSpan, IsSafeImport)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
External instance of the constraint type Monad Hsc
External instance of the constraint type Traversable []
mapM (Module, [ImportedModsVal]) -> Hsc (Module, SrcSpan, IsSafeImport)
condense [(Module, [ImportedModsVal])]
imports'
let ([(Module, SrcSpan, IsSafeImport)]
safeImps, [(Module, SrcSpan, IsSafeImport)]
regImps) = ((Module, SrcSpan, IsSafeImport) -> IsSafeImport)
-> [(Module, SrcSpan, IsSafeImport)]
-> ([(Module, SrcSpan, IsSafeImport)],
[(Module, SrcSpan, IsSafeImport)])
forall a. (a -> IsSafeImport) -> [a] -> ([a], [a])
partition (\(Module
_,SrcSpan
_,IsSafeImport
s) -> IsSafeImport
s) [(Module, SrcSpan, IsSafeImport)]
imps
WarningMessages
oldErrs <- Hsc WarningMessages
getWarnings
Hsc ()
clearWarnings
Set UnitId
safePkgs <- [UnitId] -> Set UnitId
forall a. Ord a => [a] -> Set a
External instance of the constraint type Ord UnitId
S.fromList ([UnitId] -> Set UnitId) -> Hsc [UnitId] -> Hsc (Set UnitId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
<$> ((Module, SrcSpan, IsSafeImport) -> Hsc (Maybe UnitId))
-> [(Module, SrcSpan, IsSafeImport)] -> Hsc [UnitId]
forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
External instance of the constraint type Applicative Hsc
mapMaybeM (Module, SrcSpan, IsSafeImport) -> Hsc (Maybe UnitId)
forall a. (Module, SrcSpan, a) -> Hsc (Maybe UnitId)
checkSafe [(Module, SrcSpan, IsSafeImport)]
safeImps
WarningMessages
safeErrs <- Hsc WarningMessages
getWarnings
Hsc ()
clearWarnings
(WarningMessages
infErrs, Set UnitId
infPkgs) <- case (DynFlags -> IsSafeImport
safeInferOn DynFlags
dflags) of
IsSafeImport
False -> (WarningMessages, Set UnitId) -> Hsc (WarningMessages, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (WarningMessages
forall a. Bag a
emptyBag, Set UnitId
forall a. Set a
S.empty)
IsSafeImport
True -> do Set UnitId
infPkgs <- [UnitId] -> Set UnitId
forall a. Ord a => [a] -> Set a
External instance of the constraint type Ord UnitId
S.fromList ([UnitId] -> Set UnitId) -> Hsc [UnitId] -> Hsc (Set UnitId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
<$> ((Module, SrcSpan, IsSafeImport) -> Hsc (Maybe UnitId))
-> [(Module, SrcSpan, IsSafeImport)] -> Hsc [UnitId]
forall (m :: * -> *) a b.
Applicative m =>
(a -> m (Maybe b)) -> [a] -> m [b]
External instance of the constraint type Applicative Hsc
mapMaybeM (Module, SrcSpan, IsSafeImport) -> Hsc (Maybe UnitId)
forall a. (Module, SrcSpan, a) -> Hsc (Maybe UnitId)
checkSafe [(Module, SrcSpan, IsSafeImport)]
regImps
WarningMessages
infErrs <- Hsc WarningMessages
getWarnings
Hsc ()
clearWarnings
(WarningMessages, Set UnitId) -> Hsc (WarningMessages, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (WarningMessages
infErrs, Set UnitId
infPkgs)
WarningMessages -> Hsc ()
logWarnings WarningMessages
oldErrs
case (WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag WarningMessages
safeErrs) of
IsSafeImport
False -> IO TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO TcGblEnv -> Hsc TcGblEnv)
-> (WarningMessages -> IO TcGblEnv)
-> WarningMessages
-> Hsc TcGblEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceError -> IO TcGblEnv
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception SourceError
throwIO (SourceError -> IO TcGblEnv)
-> (WarningMessages -> SourceError)
-> WarningMessages
-> IO TcGblEnv
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarningMessages -> SourceError
mkSrcErr (WarningMessages -> Hsc TcGblEnv)
-> WarningMessages -> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$ WarningMessages
safeErrs
IsSafeImport
True -> do
let infPassed :: IsSafeImport
infPassed = WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag WarningMessages
infErrs
TcGblEnv
tcg_env' <- case (IsSafeImport -> IsSafeImport
not IsSafeImport
infPassed) of
IsSafeImport
True -> TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer TcGblEnv
tcg_env WarningMessages
infErrs
IsSafeImport
False -> TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_env
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (DynFlags -> IsSafeImport
packageTrustOn DynFlags
dflags) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ Set UnitId -> Hsc ()
checkPkgTrust Set UnitId
pkgReqs
let newTrust :: ImportAvails
newTrust = DynFlags
-> Set UnitId -> Set UnitId -> IsSafeImport -> ImportAvails
pkgTrustReqs DynFlags
dflags Set UnitId
safePkgs Set UnitId
infPkgs IsSafeImport
infPassed
TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_env' { tcg_imports :: ImportAvails
tcg_imports = ImportAvails
impInfo ImportAvails -> ImportAvails -> ImportAvails
`plusImportAvails` ImportAvails
newTrust }
where
impInfo :: ImportAvails
impInfo = TcGblEnv -> ImportAvails
tcg_imports TcGblEnv
tcg_env
imports :: ImportedMods
imports = ImportAvails -> ImportedMods
imp_mods ImportAvails
impInfo
imports1 :: [(Module, [ImportedBy])]
imports1 = ImportedMods -> [(Module, [ImportedBy])]
forall a. ModuleEnv a -> [(Module, a)]
moduleEnvToList ImportedMods
imports
imports' :: [(Module, [ImportedModsVal])]
imports' = ((Module, [ImportedBy]) -> (Module, [ImportedModsVal]))
-> [(Module, [ImportedBy])] -> [(Module, [ImportedModsVal])]
forall a b. (a -> b) -> [a] -> [b]
map (([ImportedBy] -> [ImportedModsVal])
-> (Module, [ImportedBy]) -> (Module, [ImportedModsVal])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall a. Functor ((,) a)
fmap [ImportedBy] -> [ImportedModsVal]
importedByUser) [(Module, [ImportedBy])]
imports1
pkgReqs :: Set UnitId
pkgReqs = ImportAvails -> Set UnitId
imp_trust_pkgs ImportAvails
impInfo
condense :: (Module, [ImportedModsVal]) -> Hsc (Module, SrcSpan, IsSafeImport)
condense :: (Module, [ImportedModsVal]) -> Hsc (Module, SrcSpan, IsSafeImport)
condense (Module
_, []) = String -> Hsc (Module, SrcSpan, IsSafeImport)
forall a. String -> a
panic String
"GHC.Driver.Main.condense: Pattern match failure!"
condense (Module
m, ImportedModsVal
x:[ImportedModsVal]
xs) = do ImportedModsVal
imv <- (ImportedModsVal -> ImportedModsVal -> Hsc ImportedModsVal)
-> ImportedModsVal -> [ImportedModsVal] -> Hsc ImportedModsVal
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
External instance of the constraint type Monad Hsc
External instance of the constraint type Foldable []
foldlM ImportedModsVal -> ImportedModsVal -> Hsc ImportedModsVal
cond' ImportedModsVal
x [ImportedModsVal]
xs
(Module, SrcSpan, IsSafeImport)
-> Hsc (Module, SrcSpan, IsSafeImport)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Module
m, ImportedModsVal -> SrcSpan
imv_span ImportedModsVal
imv, ImportedModsVal -> IsSafeImport
imv_is_safe ImportedModsVal
imv)
cond' :: ImportedModsVal -> ImportedModsVal -> Hsc ImportedModsVal
cond' :: ImportedModsVal -> ImportedModsVal -> Hsc ImportedModsVal
cond' ImportedModsVal
v1 ImportedModsVal
v2
| ImportedModsVal -> IsSafeImport
imv_is_safe ImportedModsVal
v1 IsSafeImport -> IsSafeImport -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq IsSafeImport
/= ImportedModsVal -> IsSafeImport
imv_is_safe ImportedModsVal
v2
= do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
ErrMsg -> Hsc ImportedModsVal
forall (io :: * -> *) a. MonadIO io => ErrMsg -> io a
External instance of the constraint type MonadIO Hsc
throwOneError (ErrMsg -> Hsc ImportedModsVal) -> ErrMsg -> Hsc ImportedModsVal
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags (ImportedModsVal -> SrcSpan
imv_span ImportedModsVal
v1)
(String -> SDoc
text String
"Module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (ImportedModsVal -> ModuleName
imv_name ImportedModsVal
v1) SDoc -> SDoc -> SDoc
<+>
(String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ String
"is imported both as a safe and unsafe import!"))
| IsSafeImport
otherwise
= ImportedModsVal -> Hsc ImportedModsVal
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ImportedModsVal
v1
checkSafe :: (Module, SrcSpan, a) -> Hsc (Maybe UnitId)
checkSafe :: (Module, SrcSpan, a) -> Hsc (Maybe UnitId)
checkSafe (Module
m, SrcSpan
l, a
_) = (Maybe UnitId, Set UnitId) -> Maybe UnitId
forall a b. (a, b) -> a
fst ((Maybe UnitId, Set UnitId) -> Maybe UnitId)
-> Hsc (Maybe UnitId, Set UnitId) -> Hsc (Maybe UnitId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
`fmap` Module -> SrcSpan -> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' Module
m SrcSpan
l
pkgTrustReqs :: DynFlags -> Set UnitId -> Set UnitId ->
Bool -> ImportAvails
pkgTrustReqs :: DynFlags
-> Set UnitId -> Set UnitId -> IsSafeImport -> ImportAvails
pkgTrustReqs DynFlags
dflags Set UnitId
req Set UnitId
inf IsSafeImport
infPassed | DynFlags -> IsSafeImport
safeInferOn DynFlags
dflags
IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport -> IsSafeImport
not (DynFlags -> IsSafeImport
safeHaskellModeEnabled DynFlags
dflags) IsSafeImport -> IsSafeImport -> IsSafeImport
&& IsSafeImport
infPassed
= ImportAvails
emptyImportAvails {
imp_trust_pkgs :: Set UnitId
imp_trust_pkgs = Set UnitId
req Set UnitId -> Set UnitId -> Set UnitId
forall a. Ord a => Set a -> Set a -> Set a
External instance of the constraint type Ord UnitId
`S.union` Set UnitId
inf
}
pkgTrustReqs DynFlags
dflags Set UnitId
_ Set UnitId
_ IsSafeImport
_ | DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags SafeHaskellMode -> SafeHaskellMode -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
== SafeHaskellMode
Sf_Unsafe
= ImportAvails
emptyImportAvails
pkgTrustReqs DynFlags
_ Set UnitId
req Set UnitId
_ IsSafeImport
_ = ImportAvails
emptyImportAvails { imp_trust_pkgs :: Set UnitId
imp_trust_pkgs = Set UnitId
req }
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO Bool
hscCheckSafe :: HscEnv -> Module -> SrcSpan -> IO IsSafeImport
hscCheckSafe HscEnv
hsc_env Module
m SrcSpan
l = HscEnv -> Hsc IsSafeImport -> IO IsSafeImport
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc IsSafeImport -> IO IsSafeImport)
-> Hsc IsSafeImport -> IO IsSafeImport
forall a b. (a -> b) -> a -> b
$ do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
Set UnitId
pkgs <- (Maybe UnitId, Set UnitId) -> Set UnitId
forall a b. (a, b) -> b
snd ((Maybe UnitId, Set UnitId) -> Set UnitId)
-> Hsc (Maybe UnitId, Set UnitId) -> Hsc (Set UnitId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
`fmap` Module -> SrcSpan -> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' Module
m SrcSpan
l
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (DynFlags -> IsSafeImport
packageTrustOn DynFlags
dflags) (Hsc () -> Hsc ()) -> Hsc () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ Set UnitId -> Hsc ()
checkPkgTrust Set UnitId
pkgs
WarningMessages
errs <- Hsc WarningMessages
getWarnings
IsSafeImport -> Hsc IsSafeImport
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (IsSafeImport -> Hsc IsSafeImport)
-> IsSafeImport -> Hsc IsSafeImport
forall a b. (a -> b) -> a -> b
$ WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag WarningMessages
errs
hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (Bool, Set UnitId)
hscGetSafe :: HscEnv -> Module -> SrcSpan -> IO (IsSafeImport, Set UnitId)
hscGetSafe HscEnv
hsc_env Module
m SrcSpan
l = HscEnv
-> Hsc (IsSafeImport, Set UnitId) -> IO (IsSafeImport, Set UnitId)
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc (IsSafeImport, Set UnitId) -> IO (IsSafeImport, Set UnitId))
-> Hsc (IsSafeImport, Set UnitId) -> IO (IsSafeImport, Set UnitId)
forall a b. (a -> b) -> a -> b
$ do
(Maybe UnitId
self, Set UnitId
pkgs) <- Module -> SrcSpan -> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' Module
m SrcSpan
l
IsSafeImport
good <- WarningMessages -> IsSafeImport
forall a. Bag a -> IsSafeImport
isEmptyBag (WarningMessages -> IsSafeImport)
-> Hsc WarningMessages -> Hsc IsSafeImport
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
`fmap` Hsc WarningMessages
getWarnings
Hsc ()
clearWarnings
let pkgs' :: Set UnitId
pkgs' | Just UnitId
p <- Maybe UnitId
self = UnitId -> Set UnitId -> Set UnitId
forall a. Ord a => a -> Set a -> Set a
External instance of the constraint type Ord UnitId
S.insert UnitId
p Set UnitId
pkgs
| IsSafeImport
otherwise = Set UnitId
pkgs
(IsSafeImport, Set UnitId) -> Hsc (IsSafeImport, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (IsSafeImport
good, Set UnitId
pkgs')
hscCheckSafe' :: Module -> SrcSpan
-> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' :: Module -> SrcSpan -> Hsc (Maybe UnitId, Set UnitId)
hscCheckSafe' Module
m SrcSpan
l = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
(IsSafeImport
tw, Set UnitId
pkgs) <- Module -> SrcSpan -> Hsc (IsSafeImport, Set UnitId)
isModSafe Module
m SrcSpan
l
case IsSafeImport
tw of
IsSafeImport
False -> (Maybe UnitId, Set UnitId) -> Hsc (Maybe UnitId, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Maybe UnitId
forall a. Maybe a
Nothing, Set UnitId
pkgs)
IsSafeImport
True | DynFlags -> Module -> IsSafeImport
isHomePkg DynFlags
dflags Module
m -> (Maybe UnitId, Set UnitId) -> Hsc (Maybe UnitId, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Maybe UnitId
forall a. Maybe a
Nothing, Set UnitId
pkgs)
| IsSafeImport
otherwise -> (Maybe UnitId, Set UnitId) -> Hsc (Maybe UnitId, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (UnitId -> Maybe UnitId
forall a. a -> Maybe a
Just (UnitId -> Maybe UnitId) -> UnitId -> Maybe UnitId
forall a b. (a -> b) -> a -> b
$ Unit -> UnitId
toUnitId (Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m), Set UnitId
pkgs)
where
isModSafe :: Module -> SrcSpan -> Hsc (Bool, Set UnitId)
isModSafe :: Module -> SrcSpan -> Hsc (IsSafeImport, Set UnitId)
isModSafe Module
m SrcSpan
l = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
Maybe ModIface
iface <- Module -> Hsc (Maybe ModIface)
lookup' Module
m
case Maybe ModIface
iface of
Maybe ModIface
Nothing -> ErrMsg -> Hsc (IsSafeImport, Set UnitId)
forall (io :: * -> *) a. MonadIO io => ErrMsg -> io a
External instance of the constraint type MonadIO Hsc
throwOneError (ErrMsg -> Hsc (IsSafeImport, Set UnitId))
-> ErrMsg -> Hsc (IsSafeImport, Set UnitId)
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags SrcSpan
l
(SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Can't load the interface file for" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
m
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
", to check that it can be safely imported"
Just ModIface
iface' ->
let trust :: SafeHaskellMode
trust = IfaceTrustInfo -> SafeHaskellMode
getSafeMode (IfaceTrustInfo -> SafeHaskellMode)
-> IfaceTrustInfo -> SafeHaskellMode
forall a b. (a -> b) -> a -> b
$ ModIface -> IfaceTrustInfo
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust ModIface
iface'
trust_own_pkg :: IsSafeImport
trust_own_pkg = ModIface -> IsSafeImport
forall (phase :: ModIfacePhase). ModIface_ phase -> IsSafeImport
mi_trust_pkg ModIface
iface'
safeM :: IsSafeImport
safeM = SafeHaskellMode
trust SafeHaskellMode -> [SafeHaskellMode] -> IsSafeImport
forall (t :: * -> *) a.
(Foldable t, Eq a) =>
a -> t a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
External instance of the constraint type Foldable []
`elem` [SafeHaskellMode
Sf_Safe, SafeHaskellMode
Sf_SafeInferred, SafeHaskellMode
Sf_Trustworthy]
safeP :: IsSafeImport
safeP = DynFlags
-> SafeHaskellMode -> IsSafeImport -> Module -> IsSafeImport
packageTrusted DynFlags
dflags SafeHaskellMode
trust IsSafeImport
trust_own_pkg Module
m
pkgRs :: Set UnitId
pkgRs = [UnitId] -> Set UnitId
forall a. Ord a => [a] -> Set a
External instance of the constraint type Ord UnitId
S.fromList ([UnitId] -> Set UnitId)
-> ([(UnitId, IsSafeImport)] -> [UnitId])
-> [(UnitId, IsSafeImport)]
-> Set UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnitId, IsSafeImport) -> UnitId)
-> [(UnitId, IsSafeImport)] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (UnitId, IsSafeImport) -> UnitId
forall a b. (a, b) -> a
fst ([(UnitId, IsSafeImport)] -> Set UnitId)
-> [(UnitId, IsSafeImport)] -> Set UnitId
forall a b. (a -> b) -> a -> b
$ ((UnitId, IsSafeImport) -> IsSafeImport)
-> [(UnitId, IsSafeImport)] -> [(UnitId, IsSafeImport)]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter (UnitId, IsSafeImport) -> IsSafeImport
forall a b. (a, b) -> b
snd ([(UnitId, IsSafeImport)] -> [(UnitId, IsSafeImport)])
-> [(UnitId, IsSafeImport)] -> [(UnitId, IsSafeImport)]
forall a b. (a -> b) -> a -> b
$ Dependencies -> [(UnitId, IsSafeImport)]
dep_pkgs (Dependencies -> [(UnitId, IsSafeImport)])
-> Dependencies -> [(UnitId, IsSafeImport)]
forall a b. (a -> b) -> a -> b
$ ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface'
warns :: WarningMessages
warns = if WarningFlag -> DynFlags -> IsSafeImport
wopt WarningFlag
Opt_WarnInferredSafeImports DynFlags
dflags
IsSafeImport -> IsSafeImport -> IsSafeImport
&& DynFlags -> IsSafeImport
safeLanguageOn DynFlags
dflags
IsSafeImport -> IsSafeImport -> IsSafeImport
&& SafeHaskellMode
trust SafeHaskellMode -> SafeHaskellMode -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
== SafeHaskellMode
Sf_SafeInferred
then WarningMessages
inferredImportWarn
else WarningMessages
forall a. Bag a
emptyBag
errs :: WarningMessages
errs = case (IsSafeImport
safeM, IsSafeImport
safeP) of
(IsSafeImport
True, IsSafeImport
True ) -> WarningMessages
forall a. Bag a
emptyBag
(IsSafeImport
True, IsSafeImport
False) -> WarningMessages
pkgTrustErr
(IsSafeImport
False, IsSafeImport
_ ) -> WarningMessages
modTrustErr
in do
WarningMessages -> Hsc ()
logWarnings WarningMessages
warns
WarningMessages -> Hsc ()
logWarnings WarningMessages
errs
(IsSafeImport, Set UnitId) -> Hsc (IsSafeImport, Set UnitId)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (SafeHaskellMode
trust SafeHaskellMode -> SafeHaskellMode -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq SafeHaskellMode
== SafeHaskellMode
Sf_Trustworthy, Set UnitId
pkgRs)
where
inferredImportWarn :: WarningMessages
inferredImportWarn = ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag
(ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$ WarnReason -> ErrMsg -> ErrMsg
makeIntoWarning (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnInferredSafeImports)
(ErrMsg -> ErrMsg) -> ErrMsg -> ErrMsg
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> ErrMsg
mkErrMsg DynFlags
dflags SrcSpan
l (DynFlags -> PrintUnqualified
pkgQual DynFlags
dflags)
(SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
sep
[ String -> SDoc
text String
"Importing Safe-Inferred module "
SDoc -> SDoc -> SDoc
<> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m)
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
" from explicitly Safe module"
]
pkgTrustErr :: WarningMessages
pkgTrustErr = ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> ErrMsg
mkErrMsg DynFlags
dflags SrcSpan
l (DynFlags -> PrintUnqualified
pkgQual DynFlags
dflags) (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
sep [ ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m)
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
": Can't be safely imported!"
, String -> SDoc
text String
"The package (" SDoc -> SDoc -> SDoc
<> Unit -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unit
ppr (Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m)
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
") the module resides in isn't trusted."
]
modTrustErr :: WarningMessages
modTrustErr = ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> ErrMsg
mkErrMsg DynFlags
dflags SrcSpan
l (DynFlags -> PrintUnqualified
pkgQual DynFlags
dflags) (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
[SDoc] -> SDoc
sep [ ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
m)
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
": Can't be safely imported!"
, String -> SDoc
text String
"The module itself isn't safe." ]
packageTrusted :: DynFlags -> SafeHaskellMode -> Bool -> Module -> Bool
packageTrusted :: DynFlags
-> SafeHaskellMode -> IsSafeImport -> Module -> IsSafeImport
packageTrusted DynFlags
_ SafeHaskellMode
Sf_None IsSafeImport
_ Module
_ = IsSafeImport
False
packageTrusted DynFlags
_ SafeHaskellMode
Sf_Ignore IsSafeImport
_ Module
_ = IsSafeImport
False
packageTrusted DynFlags
_ SafeHaskellMode
Sf_Unsafe IsSafeImport
_ Module
_ = IsSafeImport
False
packageTrusted DynFlags
dflags SafeHaskellMode
_ IsSafeImport
_ Module
_
| IsSafeImport -> IsSafeImport
not (DynFlags -> IsSafeImport
packageTrustOn DynFlags
dflags) = IsSafeImport
True
packageTrusted DynFlags
_ SafeHaskellMode
Sf_Safe IsSafeImport
False Module
_ = IsSafeImport
True
packageTrusted DynFlags
_ SafeHaskellMode
Sf_SafeInferred IsSafeImport
False Module
_ = IsSafeImport
True
packageTrusted DynFlags
dflags SafeHaskellMode
_ IsSafeImport
_ Module
m
| DynFlags -> Module -> IsSafeImport
isHomePkg DynFlags
dflags Module
m = IsSafeImport
True
| IsSafeImport
otherwise = GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> IsSafeImport
unitIsTrusted (GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport)
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport
forall a b. (a -> b) -> a -> b
$ HasDebugCallStack =>
DynFlags
-> Unit
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
DynFlags
-> Unit
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
External instance of the constraint type HasDebugCallStack
unsafeGetUnitInfo DynFlags
dflags (Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m)
lookup' :: Module -> Hsc (Maybe ModIface)
lookup' :: Module -> Hsc (Maybe ModIface)
lookup' Module
m = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
ExternalPackageState
hsc_eps <- IO ExternalPackageState -> Hsc ExternalPackageState
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ExternalPackageState -> Hsc ExternalPackageState)
-> IO ExternalPackageState -> Hsc ExternalPackageState
forall a b. (a -> b) -> a -> b
$ HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
let pkgIfaceT :: PackageIfaceTable
pkgIfaceT = ExternalPackageState -> PackageIfaceTable
eps_PIT ExternalPackageState
hsc_eps
homePkgT :: HomePackageTable
homePkgT = HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env
iface :: Maybe ModIface
iface = HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
lookupIfaceByModule HomePackageTable
homePkgT PackageIfaceTable
pkgIfaceT Module
m
Maybe ModIface
iface' <- case Maybe ModIface
iface of
Just ModIface
_ -> Maybe ModIface -> Hsc (Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return Maybe ModIface
iface
Maybe ModIface
Nothing -> ((WarningMessages, WarningMessages), Maybe ModIface)
-> Maybe ModIface
forall a b. (a, b) -> b
snd (((WarningMessages, WarningMessages), Maybe ModIface)
-> Maybe ModIface)
-> Hsc ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc (Maybe ModIface)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Hsc
`fmap` (IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ((WarningMessages, WarningMessages), Maybe ModIface)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ((WarningMessages, WarningMessages), Maybe ModIface))
-> IO ((WarningMessages, WarningMessages), Maybe ModIface)
-> Hsc ((WarningMessages, WarningMessages), Maybe ModIface)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Module
-> IO ((WarningMessages, WarningMessages), Maybe ModIface)
getModuleInterface HscEnv
hsc_env Module
m)
Maybe ModIface -> Hsc (Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return Maybe ModIface
iface'
isHomePkg :: DynFlags -> Module -> Bool
isHomePkg :: DynFlags -> Module -> IsSafeImport
isHomePkg DynFlags
dflags Module
m
| DynFlags -> Unit
thisPackage DynFlags
dflags Unit -> Unit -> IsSafeImport
forall a. Eq a => a -> a -> IsSafeImport
External instance of the constraint type Eq Unit
== Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
m = IsSafeImport
True
| IsSafeImport
otherwise = IsSafeImport
False
checkPkgTrust :: Set UnitId -> Hsc ()
checkPkgTrust :: Set UnitId -> Hsc ()
checkPkgTrust Set UnitId
pkgs = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
let errors :: [ErrMsg]
errors = (UnitId -> [ErrMsg] -> [ErrMsg])
-> [ErrMsg] -> Set UnitId -> [ErrMsg]
forall a b. (a -> b -> b) -> b -> Set a -> b
S.foldr UnitId -> [ErrMsg] -> [ErrMsg]
go [] Set UnitId
pkgs
go :: UnitId -> [ErrMsg] -> [ErrMsg]
go UnitId
pkg [ErrMsg]
acc
| GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> IsSafeImport
unitIsTrusted (GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport)
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
-> IsSafeImport
forall a b. (a -> b) -> a -> b
$ HasDebugCallStack =>
PackageState
-> UnitId
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
PackageState
-> UnitId
-> GenericUnitInfo
(Indefinite UnitId) PackageId PackageName UnitId ModuleName Module
External instance of the constraint type HasDebugCallStack
getInstalledPackageDetails (DynFlags -> PackageState
pkgState DynFlags
dflags) UnitId
pkg
= [ErrMsg]
acc
| IsSafeImport
otherwise
= (ErrMsg -> [ErrMsg] -> [ErrMsg]
forall a. a -> [a] -> [a]
:[ErrMsg]
acc) (ErrMsg -> [ErrMsg]) -> ErrMsg -> [ErrMsg]
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> PrintUnqualified -> SDoc -> ErrMsg
mkErrMsg DynFlags
dflags SrcSpan
noSrcSpan (DynFlags -> PrintUnqualified
pkgQual DynFlags
dflags)
(SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"The package (" SDoc -> SDoc -> SDoc
<> UnitId -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable UnitId
ppr UnitId
pkg SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
") is required" SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" to be trusted but it isn't!"
case [ErrMsg]
errors of
[] -> () -> Hsc ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ()
[ErrMsg]
_ -> (IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> ([ErrMsg] -> IO ()) -> [ErrMsg] -> Hsc ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceError -> IO ()
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception SourceError
throwIO (SourceError -> IO ())
-> ([ErrMsg] -> SourceError) -> [ErrMsg] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarningMessages -> SourceError
mkSrcErr (WarningMessages -> SourceError)
-> ([ErrMsg] -> WarningMessages) -> [ErrMsg] -> SourceError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ErrMsg] -> WarningMessages
forall a. [a] -> Bag a
listToBag) [ErrMsg]
errors
markUnsafeInfer :: TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer :: TcGblEnv -> WarningMessages -> Hsc TcGblEnv
markUnsafeInfer TcGblEnv
tcg_env WarningMessages
whyUnsafe = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
IsSafeImport -> Hsc () -> Hsc ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative Hsc
when (WarningFlag -> DynFlags -> IsSafeImport
wopt WarningFlag
Opt_WarnUnsafe DynFlags
dflags)
(WarningMessages -> Hsc ()
logWarnings (WarningMessages -> Hsc ()) -> WarningMessages -> Hsc ()
forall a b. (a -> b) -> a -> b
$ ErrMsg -> WarningMessages
forall a. a -> Bag a
unitBag (ErrMsg -> WarningMessages) -> ErrMsg -> WarningMessages
forall a b. (a -> b) -> a -> b
$ WarnReason -> ErrMsg -> ErrMsg
makeIntoWarning (WarningFlag -> WarnReason
Reason WarningFlag
Opt_WarnUnsafe) (ErrMsg -> ErrMsg) -> ErrMsg -> ErrMsg
forall a b. (a -> b) -> a -> b
$
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainWarnMsg DynFlags
dflags (DynFlags -> SrcSpan
warnUnsafeOnLoc DynFlags
dflags) (DynFlags -> SDoc
whyUnsafe' DynFlags
dflags))
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ IORef (IsSafeImport, WarningMessages)
-> (IsSafeImport, WarningMessages) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (TcGblEnv -> IORef (IsSafeImport, WarningMessages)
tcg_safeInfer TcGblEnv
tcg_env) (IsSafeImport
False, WarningMessages
whyUnsafe)
case IsSafeImport -> IsSafeImport
not (DynFlags -> IsSafeImport
safeHaskellModeEnabled DynFlags
dflags) of
IsSafeImport
True -> TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (TcGblEnv -> Hsc TcGblEnv) -> TcGblEnv -> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$ TcGblEnv
tcg_env { tcg_imports :: ImportAvails
tcg_imports = ImportAvails
wiped_trust }
IsSafeImport
False -> TcGblEnv -> Hsc TcGblEnv
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return TcGblEnv
tcg_env
where
wiped_trust :: ImportAvails
wiped_trust = (TcGblEnv -> ImportAvails
tcg_imports TcGblEnv
tcg_env) { imp_trust_pkgs :: Set UnitId
imp_trust_pkgs = Set UnitId
forall a. Set a
S.empty }
pprMod :: SDoc
pprMod = ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable ModuleName
ppr (ModuleName -> SDoc) -> ModuleName -> SDoc
forall a b. (a -> b) -> a -> b
$ Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (Module -> ModuleName) -> Module -> ModuleName
forall a b. (a -> b) -> a -> b
$ TcGblEnv -> Module
tcg_mod TcGblEnv
tcg_env
whyUnsafe' :: DynFlags -> SDoc
whyUnsafe' DynFlags
df = [SDoc] -> SDoc
vcat [ SDoc -> SDoc
quotes SDoc
pprMod SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"has been inferred as unsafe!"
, String -> SDoc
text String
"Reason:"
, Int -> SDoc -> SDoc
nest Int
4 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ ([SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ DynFlags -> [SDoc]
badFlags DynFlags
df) SDoc -> SDoc -> SDoc
$+$
([SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ WarningMessages -> [SDoc]
pprErrMsgBagWithLoc WarningMessages
whyUnsafe) SDoc -> SDoc -> SDoc
$+$
([SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ [ClsInst] -> [SDoc]
forall {t :: * -> *}. Foldable t => t ClsInst -> [SDoc]
External instance of the constraint type Foldable []
badInsts ([ClsInst] -> [SDoc]) -> [ClsInst] -> [SDoc]
forall a b. (a -> b) -> a -> b
$ TcGblEnv -> [ClsInst]
tcg_insts TcGblEnv
tcg_env)
]
badFlags :: DynFlags -> [SDoc]
badFlags DynFlags
df = ((String, DynFlags -> SrcSpan, DynFlags -> IsSafeImport,
DynFlags -> DynFlags)
-> [SDoc])
-> [(String, DynFlags -> SrcSpan, DynFlags -> IsSafeImport,
DynFlags -> DynFlags)]
-> [SDoc]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
External instance of the constraint type Foldable []
concatMap (DynFlags
-> (String, DynFlags -> SrcSpan, DynFlags -> IsSafeImport,
DynFlags -> DynFlags)
-> [SDoc]
forall {t} {d}.
t -> (String, t -> SrcSpan, t -> IsSafeImport, d) -> [SDoc]
badFlag DynFlags
df) [(String, DynFlags -> SrcSpan, DynFlags -> IsSafeImport,
DynFlags -> DynFlags)]
unsafeFlagsForInfer
badFlag :: t -> (String, t -> SrcSpan, t -> IsSafeImport, d) -> [SDoc]
badFlag t
df (String
str,t -> SrcSpan
loc,t -> IsSafeImport
on,d
_)
| t -> IsSafeImport
on t
df = [Severity -> SrcSpan -> SDoc -> SDoc
mkLocMessage Severity
SevOutput (t -> SrcSpan
loc t
df) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
str SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"is not allowed in Safe Haskell"]
| IsSafeImport
otherwise = []
badInsts :: t ClsInst -> [SDoc]
badInsts t ClsInst
insts = (ClsInst -> [SDoc]) -> t ClsInst -> [SDoc]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
Evidence bound by a type signature of the constraint type Foldable t
concatMap ClsInst -> [SDoc]
badInst t ClsInst
insts
checkOverlap :: OverlapMode -> IsSafeImport
checkOverlap (NoOverlap SourceText
_) = IsSafeImport
False
checkOverlap OverlapMode
_ = IsSafeImport
True
badInst :: ClsInst -> [SDoc]
badInst ClsInst
ins | OverlapMode -> IsSafeImport
checkOverlap (OverlapFlag -> OverlapMode
overlapMode (ClsInst -> OverlapFlag
is_flag ClsInst
ins))
= [Severity -> SrcSpan -> SDoc -> SDoc
mkLocMessage Severity
SevOutput (Name -> SrcSpan
nameSrcSpan (Name -> SrcSpan) -> Name -> SrcSpan
forall a b. (a -> b) -> a -> b
$ Id -> Name
forall a. NamedThing a => a -> Name
External instance of the constraint type NamedThing Id
getName (Id -> Name) -> Id -> Name
forall a b. (a -> b) -> a -> b
$ ClsInst -> Id
is_dfun ClsInst
ins) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
OverlapMode -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable OverlapMode
ppr (OverlapFlag -> OverlapMode
overlapMode (OverlapFlag -> OverlapMode) -> OverlapFlag -> OverlapMode
forall a b. (a -> b) -> a -> b
$ ClsInst -> OverlapFlag
is_flag ClsInst
ins) SDoc -> SDoc -> SDoc
<+>
String -> SDoc
text String
"overlap mode isn't allowed in Safe Haskell"]
| IsSafeImport
otherwise = []
hscGetSafeMode :: TcGblEnv -> Hsc SafeHaskellMode
hscGetSafeMode :: TcGblEnv -> Hsc SafeHaskellMode
hscGetSafeMode TcGblEnv
tcg_env = do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
IO SafeHaskellMode -> Hsc SafeHaskellMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO SafeHaskellMode -> Hsc SafeHaskellMode)
-> IO SafeHaskellMode -> Hsc SafeHaskellMode
forall a b. (a -> b) -> a -> b
$ DynFlags -> TcGblEnv -> IO SafeHaskellMode
finalSafeMode DynFlags
dflags TcGblEnv
tcg_env
hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts
hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts
hscSimplify HscEnv
hsc_env [String]
plugins ModGuts
modguts =
HscEnv -> Hsc ModGuts -> IO ModGuts
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc ModGuts -> IO ModGuts) -> Hsc ModGuts -> IO ModGuts
forall a b. (a -> b) -> a -> b
$ [String] -> ModGuts -> Hsc ModGuts
hscSimplify' [String]
plugins ModGuts
modguts
hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts
hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts
hscSimplify' [String]
plugins ModGuts
ds_result = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
let hsc_env_with_plugins :: HscEnv
hsc_env_with_plugins = HscEnv
hsc_env
{ hsc_dflags :: DynFlags
hsc_dflags = (String -> DynFlags -> DynFlags)
-> DynFlags -> [String] -> DynFlags
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr String -> DynFlags -> DynFlags
addPluginModuleName (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) [String]
plugins
}
{-# SCC "Core2Core" #-}
IO ModGuts -> Hsc ModGuts
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ModGuts -> Hsc ModGuts) -> IO ModGuts -> Hsc ModGuts
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO ModGuts
core2core HscEnv
hsc_env_with_plugins ModGuts
ds_result
hscSimpleIface :: HscEnv
-> TcGblEnv
-> Maybe Fingerprint
-> IO (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface :: HscEnv
-> TcGblEnv
-> Maybe Fingerprint
-> IO (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface HscEnv
hsc_env TcGblEnv
tc_result Maybe Fingerprint
mb_old_iface
= HscEnv
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
-> IO (ModIface, Maybe Fingerprint, ModDetails)
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc (ModIface, Maybe Fingerprint, ModDetails)
-> IO (ModIface, Maybe Fingerprint, ModDetails))
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
-> IO (ModIface, Maybe Fingerprint, ModDetails)
forall a b. (a -> b) -> a -> b
$ TcGblEnv
-> Maybe Fingerprint
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface' TcGblEnv
tc_result Maybe Fingerprint
mb_old_iface
hscSimpleIface' :: TcGblEnv
-> Maybe Fingerprint
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface' :: TcGblEnv
-> Maybe Fingerprint
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
hscSimpleIface' TcGblEnv
tc_result Maybe Fingerprint
mb_old_iface = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
ModDetails
details <- IO ModDetails -> Hsc ModDetails
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ModDetails -> Hsc ModDetails)
-> IO ModDetails -> Hsc ModDetails
forall a b. (a -> b) -> a -> b
$ HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc HscEnv
hsc_env TcGblEnv
tc_result
SafeHaskellMode
safe_mode <- TcGblEnv -> Hsc SafeHaskellMode
hscGetSafeMode TcGblEnv
tc_result
ModIface
new_iface
<- {-# SCC "MkFinalIface" #-}
IO ModIface -> Hsc ModIface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ModIface -> Hsc ModIface) -> IO ModIface -> Hsc ModIface
forall a b. (a -> b) -> a -> b
$
HscEnv -> SafeHaskellMode -> ModDetails -> TcGblEnv -> IO ModIface
mkIfaceTc HscEnv
hsc_env SafeHaskellMode
safe_mode ModDetails
details TcGblEnv
tc_result
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ HscEnv -> IO ()
dumpIfaceStats HscEnv
hsc_env
(ModIface, Maybe Fingerprint, ModDetails)
-> Hsc (ModIface, Maybe Fingerprint, ModDetails)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (ModIface
new_iface, Maybe Fingerprint
mb_old_iface, ModDetails
details)
hscWriteIface :: DynFlags -> ModIface -> Bool -> ModLocation -> IO ()
hscWriteIface :: DynFlags -> ModIface -> IsSafeImport -> ModLocation -> IO ()
hscWriteIface DynFlags
dflags ModIface
iface IsSafeImport
no_change ModLocation
mod_location = do
let ifaceBaseFile :: String
ifaceBaseFile = ModLocation -> String
ml_hi_file ModLocation
mod_location
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
unless IsSafeImport
no_change (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
let ifaceFile :: String
ifaceFile = String -> String -> String
buildIfName String
ifaceBaseFile (DynFlags -> String
hiSuf DynFlags
dflags)
in {-# SCC "writeIface" #-}
DynFlags -> String -> ModIface -> IO ()
writeIface DynFlags
dflags String
ifaceFile ModIface
iface
DynFlags -> IO () -> IO ()
forall (m :: * -> *). MonadIO m => DynFlags -> m () -> m ()
External instance of the constraint type MonadIO IO
whenGeneratingDynamicToo DynFlags
dflags (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let dynDflags :: DynFlags
dynDflags = DynFlags -> DynFlags
dynamicTooMkDynamicDynFlags DynFlags
dflags
dynIfaceFile :: String
dynIfaceFile = String -> String -> String
buildIfName String
ifaceBaseFile (DynFlags -> String
hiSuf DynFlags
dynDflags)
DynFlags -> String -> ModIface -> IO ()
writeIface DynFlags
dynDflags String
dynIfaceFile ModIface
iface
where
buildIfName :: String -> String -> String
buildIfName :: String -> String -> String
buildIfName String
baseName String
suffix
| Just String
name <- DynFlags -> Maybe String
outputHi DynFlags
dflags
= String
name
| IsSafeImport
otherwise
= let with_hi :: String
with_hi = String -> String -> String
replaceExtension String
baseName String
suffix
in IsSafeImport -> String -> String
addBootSuffix_maybe (ModIface -> IsSafeImport
mi_boot ModIface
iface) String
with_hi
hscGenHardCode :: HscEnv -> CgGuts -> ModLocation -> FilePath
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)], NonCaffySet)
hscGenHardCode :: HscEnv
-> CgGuts
-> ModLocation
-> String
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
hscGenHardCode HscEnv
hsc_env CgGuts
cgguts ModLocation
location String
output_filename = do
let CgGuts{
cg_module :: CgGuts -> Module
cg_module = Module
this_mod,
cg_binds :: CgGuts -> CoreProgram
cg_binds = CoreProgram
core_binds,
cg_tycons :: CgGuts -> [TyCon]
cg_tycons = [TyCon]
tycons,
cg_foreign :: CgGuts -> ForeignStubs
cg_foreign = ForeignStubs
foreign_stubs0,
cg_foreign_files :: CgGuts -> [(ForeignSrcLang, String)]
cg_foreign_files = [(ForeignSrcLang, String)]
foreign_files,
cg_dep_pkgs :: CgGuts -> [UnitId]
cg_dep_pkgs = [UnitId]
dependencies,
cg_hpc_info :: CgGuts -> HpcInfo
cg_hpc_info = HpcInfo
hpc_info } = CgGuts
cgguts
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
data_tycons :: [TyCon]
data_tycons = (TyCon -> IsSafeImport) -> [TyCon] -> [TyCon]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter TyCon -> IsSafeImport
isDataTyCon [TyCon]
tycons
(CoreProgram
prepd_binds, Set CostCentre
local_ccs) <- {-# SCC "CorePrep" #-}
HscEnv
-> Module
-> ModLocation
-> CoreProgram
-> [TyCon]
-> IO (CoreProgram, Set CostCentre)
corePrepPgm HscEnv
hsc_env Module
this_mod ModLocation
location
CoreProgram
core_binds [TyCon]
data_tycons
([StgTopBinding]
stg_binds, ([CostCentre]
caf_ccs, [CostCentreStack]
caf_cc_stacks))
<- {-# SCC "CoreToStg" #-}
DynFlags
-> Module -> CoreProgram -> IO ([StgTopBinding], CollectedCCs)
myCoreToStg DynFlags
dflags Module
this_mod CoreProgram
prepd_binds
let cost_centre_info :: CollectedCCs
cost_centre_info =
(Set CostCentre -> [CostCentre]
forall a. Set a -> [a]
S.toList Set CostCentre
local_ccs [CostCentre] -> [CostCentre] -> [CostCentre]
forall a. [a] -> [a] -> [a]
++ [CostCentre]
caf_ccs, [CostCentreStack]
caf_cc_stacks)
prof_init :: SDoc
prof_init = DynFlags -> Module -> CollectedCCs -> SDoc
profilingInitCode DynFlags
dflags Module
this_mod CollectedCCs
cost_centre_info
foreign_stubs :: ForeignStubs
foreign_stubs = ForeignStubs
foreign_stubs0 ForeignStubs -> SDoc -> ForeignStubs
`appendStubC` SDoc
prof_init
DynFlags
-> SDoc
-> ((String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> ())
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
forall (m :: * -> *) a.
MonadIO m =>
DynFlags -> SDoc -> (a -> ()) -> m a -> m a
External instance of the constraint type MonadIO IO
withTiming DynFlags
dflags
(String -> SDoc
text String
"CodeGen"SDoc -> SDoc -> SDoc
<+>SDoc -> SDoc
brackets (Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
this_mod))
(()
-> (String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> ()
forall a b. a -> b -> a
const ()) (IO (String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet))
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
forall a b. (a -> b) -> a -> b
$ do
Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
cmms <- {-# SCC "StgToCmm" #-}
HscEnv
-> Module
-> [TyCon]
-> CollectedCCs
-> [StgTopBinding]
-> HpcInfo
-> IO
(Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet)
doCodeGen HscEnv
hsc_env Module
this_mod [TyCon]
data_tycons
CollectedCCs
cost_centre_info
[StgTopBinding]
stg_binds HpcInfo
hpc_info
Stream IO RawCmmGroup NonCaffySet
rawcmms0 <- {-# SCC "cmmToRawCmm" #-}
(Hooks
-> Maybe
(DynFlags
-> Maybe Module
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO (Stream IO RawCmmGroup NonCaffySet)))
-> (DynFlags
-> Maybe Module
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO (Stream IO RawCmmGroup NonCaffySet))
-> DynFlags
-> DynFlags
-> Maybe Module
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO (Stream IO RawCmmGroup NonCaffySet)
forall a. (Hooks -> Maybe a) -> a -> DynFlags -> a
lookupHook Hooks
-> Maybe
(DynFlags
-> Maybe Module
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO (Stream IO RawCmmGroup NonCaffySet))
Hooks
-> forall a.
Maybe
(DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] a
-> IO (Stream IO RawCmmGroup a))
cmmToRawCmmHook
(\DynFlags
dflg Maybe Module
_ -> DynFlags
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO (Stream IO RawCmmGroup NonCaffySet)
forall a.
DynFlags
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] a
-> IO (Stream IO RawCmmGroup a)
cmmToRawCmm DynFlags
dflg) DynFlags
dflags DynFlags
dflags (Module -> Maybe Module
forall a. a -> Maybe a
Just Module
this_mod) Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
cmms
let dump :: t a -> IO (t a)
dump t a
a = do
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
unless (t a -> IsSafeImport
forall (t :: * -> *) a. Foldable t => t a -> IsSafeImport
Evidence bound by a type signature of the constraint type Foldable t
null t a
a) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_cmm_raw String
"Raw Cmm" DumpFormat
FormatCMM (t a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable (t a)
ppr t a
a)
t a -> IO (t a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return t a
a
rawcmms1 :: Stream IO RawCmmGroup NonCaffySet
rawcmms1 = (RawCmmGroup -> IO RawCmmGroup)
-> Stream IO RawCmmGroup NonCaffySet
-> Stream IO RawCmmGroup NonCaffySet
forall (m :: * -> *) a b x.
Monad m =>
(a -> m b) -> Stream m a x -> Stream m b x
External instance of the constraint type Monad IO
Stream.mapM RawCmmGroup -> IO RawCmmGroup
forall {t :: * -> *} {a}.
(Foldable t, Outputable (t a)) =>
t a -> IO (t a)
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type forall d info i.
(Outputable d, Outputable info, Outputable i) =>
Outputable (GenCmmDecl d info i)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type forall a. Outputable a => Outputable (LabelMap a)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type Outputable CmmGraph
External instance of the constraint type Foldable []
dump Stream IO RawCmmGroup NonCaffySet
rawcmms0
(String
output_filename, (IsSafeImport
_stub_h_exists, Maybe String
stub_c_exists), [(ForeignSrcLang, String)]
foreign_fps, NonCaffySet
caf_infos)
<- {-# SCC "codeOutput" #-}
DynFlags
-> Module
-> String
-> ModLocation
-> ForeignStubs
-> [(ForeignSrcLang, String)]
-> [UnitId]
-> Stream IO RawCmmGroup NonCaffySet
-> IO
(String, (IsSafeImport, Maybe String), [(ForeignSrcLang, String)],
NonCaffySet)
forall a.
DynFlags
-> Module
-> String
-> ModLocation
-> ForeignStubs
-> [(ForeignSrcLang, String)]
-> [UnitId]
-> Stream IO RawCmmGroup a
-> IO
(String, (IsSafeImport, Maybe String), [(ForeignSrcLang, String)],
a)
codeOutput DynFlags
dflags Module
this_mod String
output_filename ModLocation
location
ForeignStubs
foreign_stubs [(ForeignSrcLang, String)]
foreign_files [UnitId]
dependencies Stream IO RawCmmGroup NonCaffySet
rawcmms1
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
-> IO
(String, Maybe String, [(ForeignSrcLang, String)], NonCaffySet)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (String
output_filename, Maybe String
stub_c_exists, [(ForeignSrcLang, String)]
foreign_fps, NonCaffySet
caf_infos)
hscInteractive :: HscEnv
-> CgGuts
-> ModLocation
-> IO (Maybe FilePath, CompiledByteCode, [SptEntry])
hscInteractive :: HscEnv
-> CgGuts
-> ModLocation
-> IO (Maybe String, CompiledByteCode, [SptEntry])
hscInteractive HscEnv
hsc_env CgGuts
cgguts ModLocation
location = do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let CgGuts{
cg_module :: CgGuts -> Module
cg_module = Module
this_mod,
cg_binds :: CgGuts -> CoreProgram
cg_binds = CoreProgram
core_binds,
cg_tycons :: CgGuts -> [TyCon]
cg_tycons = [TyCon]
tycons,
cg_foreign :: CgGuts -> ForeignStubs
cg_foreign = ForeignStubs
foreign_stubs,
cg_modBreaks :: CgGuts -> Maybe ModBreaks
cg_modBreaks = Maybe ModBreaks
mod_breaks,
cg_spt_entries :: CgGuts -> [SptEntry]
cg_spt_entries = [SptEntry]
spt_entries } = CgGuts
cgguts
data_tycons :: [TyCon]
data_tycons = (TyCon -> IsSafeImport) -> [TyCon] -> [TyCon]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter TyCon -> IsSafeImport
isDataTyCon [TyCon]
tycons
(CoreProgram
prepd_binds, Set CostCentre
_) <- {-# SCC "CorePrep" #-}
HscEnv
-> Module
-> ModLocation
-> CoreProgram
-> [TyCon]
-> IO (CoreProgram, Set CostCentre)
corePrepPgm HscEnv
hsc_env Module
this_mod ModLocation
location CoreProgram
core_binds [TyCon]
data_tycons
CompiledByteCode
comp_bc <- HscEnv
-> Module
-> CoreProgram
-> [TyCon]
-> Maybe ModBreaks
-> IO CompiledByteCode
byteCodeGen HscEnv
hsc_env Module
this_mod CoreProgram
prepd_binds [TyCon]
data_tycons Maybe ModBreaks
mod_breaks
(IsSafeImport
_istub_h_exists, Maybe String
istub_c_exists)
<- DynFlags
-> Module
-> ModLocation
-> ForeignStubs
-> IO (IsSafeImport, Maybe String)
outputForeignStubs DynFlags
dflags Module
this_mod ModLocation
location ForeignStubs
foreign_stubs
(Maybe String, CompiledByteCode, [SptEntry])
-> IO (Maybe String, CompiledByteCode, [SptEntry])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (Maybe String
istub_c_exists, CompiledByteCode
comp_bc, [SptEntry]
spt_entries)
hscCompileCmmFile :: HscEnv -> FilePath -> FilePath -> IO ()
hscCompileCmmFile :: HscEnv -> String -> String -> IO ()
hscCompileCmmFile HscEnv
hsc_env String
filename String
output_filename = HscEnv -> Hsc () -> IO ()
forall a. HscEnv -> Hsc a -> IO a
runHsc HscEnv
hsc_env (Hsc () -> IO ()) -> Hsc () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
CmmGroup
cmm <- IO ((WarningMessages, WarningMessages), Maybe CmmGroup)
-> Hsc CmmGroup
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe CmmGroup)
-> Hsc CmmGroup)
-> IO ((WarningMessages, WarningMessages), Maybe CmmGroup)
-> Hsc CmmGroup
forall a b. (a -> b) -> a -> b
$ DynFlags
-> String
-> IO ((WarningMessages, WarningMessages), Maybe CmmGroup)
parseCmmFile DynFlags
dflags String
filename
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ do
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_cmm_verbose_by_proc String
"Parsed Cmm" DumpFormat
FormatCMM (CmmGroup -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type forall d info i.
(Outputable d, Outputable info, Outputable i) =>
Outputable (GenCmmDecl d info i)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type Outputable CmmTopInfo
External instance of the constraint type Outputable CmmGraph
ppr CmmGroup
cmm)
let
mod_name :: ModuleName
mod_name = String -> ModuleName
mkModuleName (String -> ModuleName) -> String -> ModuleName
forall a b. (a -> b) -> a -> b
$ String
"Cmm$" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
FilePath.takeFileName String
filename
cmm_mod :: Module
cmm_mod = Unit -> ModuleName -> Module
forall u. u -> ModuleName -> GenModule u
mkModule (DynFlags -> Unit
thisPackage DynFlags
dflags) ModuleName
mod_name
[GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
cmmgroup <-
(GenCmmDecl CmmStatics CmmTopInfo CmmGraph
-> IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> CmmGroup -> IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
External instance of the constraint type Monad IO
concatMapM (\GenCmmDecl CmmStatics CmmTopInfo CmmGraph
cmm -> (ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
forall a b. (a, b) -> b
snd ((ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> IO
(ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor IO
<$> HscEnv
-> ModuleSRTInfo
-> CmmGroup
-> IO
(ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
cmmPipeline HscEnv
hsc_env (Module -> ModuleSRTInfo
emptySRT Module
cmm_mod) [GenCmmDecl CmmStatics CmmTopInfo CmmGraph
cmm]) CmmGroup
cmm
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
unless ([GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] -> IsSafeImport
forall (t :: * -> *) a. Foldable t => t a -> IsSafeImport
External instance of the constraint type Foldable []
null [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
cmmgroup) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_cmm String
"Output Cmm"
DumpFormat
FormatCMM ([GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type forall d info i.
(Outputable d, Outputable info, Outputable i) =>
Outputable (GenCmmDecl d info i)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type Outputable CmmTopInfo
External instance of the constraint type Outputable CmmGraph
ppr [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
cmmgroup)
Stream IO RawCmmGroup ()
rawCmms <- (Hooks
-> Maybe
(DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
-> IO (Stream IO RawCmmGroup ())))
-> (DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
-> IO (Stream IO RawCmmGroup ()))
-> DynFlags
-> DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
-> IO (Stream IO RawCmmGroup ())
forall a. (Hooks -> Maybe a) -> a -> DynFlags -> a
lookupHook Hooks
-> Maybe
(DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
-> IO (Stream IO RawCmmGroup ()))
Hooks
-> forall a.
Maybe
(DynFlags
-> Maybe Module
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] a
-> IO (Stream IO RawCmmGroup a))
cmmToRawCmmHook
(\DynFlags
dflgs Maybe Module
_ -> DynFlags
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
-> IO (Stream IO RawCmmGroup ())
forall a.
DynFlags
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] a
-> IO (Stream IO RawCmmGroup a)
cmmToRawCmm DynFlags
dflgs) DynFlags
dflags DynFlags
dflags Maybe Module
forall a. Maybe a
Nothing ([GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
-> Stream IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ()
forall (m :: * -> *) a. Monad m => a -> Stream m a ()
External instance of the constraint type Monad IO
Stream.yield [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
cmmgroup)
(String, (IsSafeImport, Maybe String), [(ForeignSrcLang, String)],
())
_ <- DynFlags
-> Module
-> String
-> ModLocation
-> ForeignStubs
-> [(ForeignSrcLang, String)]
-> [UnitId]
-> Stream IO RawCmmGroup ()
-> IO
(String, (IsSafeImport, Maybe String), [(ForeignSrcLang, String)],
())
forall a.
DynFlags
-> Module
-> String
-> ModLocation
-> ForeignStubs
-> [(ForeignSrcLang, String)]
-> [UnitId]
-> Stream IO RawCmmGroup a
-> IO
(String, (IsSafeImport, Maybe String), [(ForeignSrcLang, String)],
a)
codeOutput DynFlags
dflags Module
cmm_mod String
output_filename ModLocation
no_loc ForeignStubs
NoStubs [] []
Stream IO RawCmmGroup ()
rawCmms
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
where
no_loc :: ModLocation
no_loc = ModLocation :: Maybe String -> String -> String -> String -> ModLocation
ModLocation{ ml_hs_file :: Maybe String
ml_hs_file = String -> Maybe String
forall a. a -> Maybe a
Just String
filename,
ml_hi_file :: String
ml_hi_file = String -> String
forall a. String -> a
panic String
"hscCompileCmmFile: no hi file",
ml_obj_file :: String
ml_obj_file = String -> String
forall a. String -> a
panic String
"hscCompileCmmFile: no obj file",
ml_hie_file :: String
ml_hie_file = String -> String
forall a. String -> a
panic String
"hscCompileCmmFile: no hie file"}
doCodeGen :: HscEnv -> Module -> [TyCon]
-> CollectedCCs
-> [StgTopBinding]
-> HpcInfo
-> IO (Stream IO CmmGroupSRTs NonCaffySet)
doCodeGen :: HscEnv
-> Module
-> [TyCon]
-> CollectedCCs
-> [StgTopBinding]
-> HpcInfo
-> IO
(Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet)
doCodeGen HscEnv
hsc_env Module
this_mod [TyCon]
data_tycons
CollectedCCs
cost_centre_info [StgTopBinding]
stg_binds HpcInfo
hpc_info = do
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let stg_binds_w_fvs :: [CgStgTopBinding]
stg_binds_w_fvs = [StgTopBinding] -> [CgStgTopBinding]
annTopBindingsFreeVars [StgTopBinding]
stg_binds
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_stg_final String
"Final STG:" DumpFormat
FormatSTG ([CgStgTopBinding] -> SDoc
forall (pass :: StgPass).
OutputablePass pass =>
[GenStgTopBinding pass] -> SDoc
External instance of the constraint type Outputable NoExtFieldSilent
External instance of the constraint type Outputable NoExtFieldSilent
External instance of the constraint type forall a. Outputable a => Outputable (UniqDSet a)
External instance of the constraint type Outputable Id
External instance of the constraint type OutputableBndr Id
pprGenStgTopBindings [CgStgTopBinding]
stg_binds_w_fvs)
let cmm_stream :: Stream IO CmmGroup ()
cmm_stream :: Stream IO CmmGroup ()
cmm_stream = [CgStgTopBinding]
stg_binds_w_fvs [CgStgTopBinding] -> Stream IO CmmGroup () -> Stream IO CmmGroup ()
forall a b. [a] -> b -> b
`seqList` {-# SCC "StgToCmm" #-}
(Hooks
-> Maybe
(DynFlags
-> Module
-> [TyCon]
-> CollectedCCs
-> [CgStgTopBinding]
-> HpcInfo
-> Stream IO CmmGroup ()))
-> (DynFlags
-> Module
-> [TyCon]
-> CollectedCCs
-> [CgStgTopBinding]
-> HpcInfo
-> Stream IO CmmGroup ())
-> DynFlags
-> DynFlags
-> Module
-> [TyCon]
-> CollectedCCs
-> [CgStgTopBinding]
-> HpcInfo
-> Stream IO CmmGroup ()
forall a. (Hooks -> Maybe a) -> a -> DynFlags -> a
lookupHook Hooks
-> Maybe
(DynFlags
-> Module
-> [TyCon]
-> CollectedCCs
-> [CgStgTopBinding]
-> HpcInfo
-> Stream IO CmmGroup ())
stgToCmmHook DynFlags
-> Module
-> [TyCon]
-> CollectedCCs
-> [CgStgTopBinding]
-> HpcInfo
-> Stream IO CmmGroup ()
StgToCmm.codeGen DynFlags
dflags DynFlags
dflags Module
this_mod [TyCon]
data_tycons
CollectedCCs
cost_centre_info [CgStgTopBinding]
stg_binds_w_fvs HpcInfo
hpc_info
let dump1 :: t a -> IO (t a)
dump1 t a
a = do
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
unless (t a -> IsSafeImport
forall (t :: * -> *) a. Foldable t => t a -> IsSafeImport
Evidence bound by a type signature of the constraint type Foldable t
null t a
a) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_cmm_from_stg
String
"Cmm produced by codegen" DumpFormat
FormatCMM (t a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable (t a)
ppr t a
a)
t a -> IO (t a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return t a
a
ppr_stream1 :: Stream IO CmmGroup ()
ppr_stream1 = (CmmGroup -> IO CmmGroup)
-> Stream IO CmmGroup () -> Stream IO CmmGroup ()
forall (m :: * -> *) a b x.
Monad m =>
(a -> m b) -> Stream m a x -> Stream m b x
External instance of the constraint type Monad IO
Stream.mapM CmmGroup -> IO CmmGroup
forall {t :: * -> *} {a}.
(Foldable t, Outputable (t a)) =>
t a -> IO (t a)
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type forall d info i.
(Outputable d, Outputable info, Outputable i) =>
Outputable (GenCmmDecl d info i)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type Outputable CmmTopInfo
External instance of the constraint type Outputable CmmGraph
External instance of the constraint type Foldable []
dump1 Stream IO CmmGroup ()
cmm_stream
pipeline_stream :: Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
pipeline_stream =
{-# SCC "cmmPipeline" #-}
(ModuleSRTInfo
-> CmmGroup
-> IO
(ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]))
-> ModuleSRTInfo
-> Stream IO CmmGroup ()
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ModuleSRTInfo
forall (m :: * -> *) c a b.
Monad m =>
(c -> a -> m (c, b)) -> c -> Stream m a () -> Stream m b c
External instance of the constraint type Monad IO
Stream.mapAccumL (HscEnv
-> ModuleSRTInfo
-> CmmGroup
-> IO
(ModuleSRTInfo, [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
cmmPipeline HscEnv
hsc_env) (Module -> ModuleSRTInfo
emptySRT Module
this_mod) Stream IO CmmGroup ()
ppr_stream1
Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] ModuleSRTInfo
-> (ModuleSRTInfo -> NonCaffySet)
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
External instance of the constraint type forall (f :: * -> *) a. Monad f => Functor (Stream f a)
External instance of the constraint type Monad IO
<&> (SRTMap -> NonCaffySet
srtMapNonCAFs (SRTMap -> NonCaffySet)
-> (ModuleSRTInfo -> SRTMap) -> ModuleSRTInfo -> NonCaffySet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleSRTInfo -> SRTMap
moduleSRTMap)
dump2 :: t a -> IO (t a)
dump2 t a
a = do
IsSafeImport -> IO () -> IO ()
forall (f :: * -> *). Applicative f => IsSafeImport -> f () -> f ()
External instance of the constraint type Applicative IO
unless (t a -> IsSafeImport
forall (t :: * -> *) a. Foldable t => t a -> IsSafeImport
Evidence bound by a type signature of the constraint type Foldable t
null t a
a) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_cmm String
"Output Cmm" DumpFormat
FormatCMM (t a -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable (t a)
ppr t a
a)
t a -> IO (t a)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return t a
a
Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> IO
(Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (([GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
-> IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph])
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
-> Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
forall (m :: * -> *) a b x.
Monad m =>
(a -> m b) -> Stream m a x -> Stream m b x
External instance of the constraint type Monad IO
Stream.mapM [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
-> IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph]
forall {t :: * -> *} {a}.
(Foldable t, Outputable (t a)) =>
t a -> IO (t a)
External instance of the constraint type forall a. Outputable a => Outputable [a]
External instance of the constraint type forall d info i.
(Outputable d, Outputable info, Outputable i) =>
Outputable (GenCmmDecl d info i)
External instance of the constraint type forall (a :: IsSafeImport). Outputable (GenCmmStatics a)
External instance of the constraint type Outputable CmmTopInfo
External instance of the constraint type Outputable CmmGraph
External instance of the constraint type Foldable []
dump2 Stream
IO [GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph] NonCaffySet
pipeline_stream)
myCoreToStg :: DynFlags -> Module -> CoreProgram
-> IO ( [StgTopBinding]
, CollectedCCs )
myCoreToStg :: DynFlags
-> Module -> CoreProgram -> IO ([StgTopBinding], CollectedCCs)
myCoreToStg DynFlags
dflags Module
this_mod CoreProgram
prepd_binds = do
let ([StgTopBinding]
stg_binds, CollectedCCs
cost_centre_info)
= {-# SCC "Core2Stg" #-}
DynFlags
-> Module -> CoreProgram -> ([StgTopBinding], CollectedCCs)
coreToStg DynFlags
dflags Module
this_mod CoreProgram
prepd_binds
[StgTopBinding]
stg_binds2
<- {-# SCC "Stg2Stg" #-}
DynFlags -> Module -> [StgTopBinding] -> IO [StgTopBinding]
stg2stg DynFlags
dflags Module
this_mod [StgTopBinding]
stg_binds
([StgTopBinding], CollectedCCs)
-> IO ([StgTopBinding], CollectedCCs)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ([StgTopBinding]
stg_binds2, CollectedCCs
cost_centre_info)
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscStmt :: HscEnv -> String -> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscStmt HscEnv
hsc_env String
stmt = HscEnv
-> String
-> String
-> Int
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscStmtWithLocation HscEnv
hsc_env String
stmt String
"<interactive>" Int
1
hscStmtWithLocation :: HscEnv
-> String
-> String
-> Int
-> IO ( Maybe ([Id]
, ForeignHValue
, FixityEnv))
hscStmtWithLocation :: HscEnv
-> String
-> String
-> Int
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscStmtWithLocation HscEnv
hsc_env0 String
stmt String
source Int
linenumber =
HscEnv
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv)))
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ do
Maybe (LStmt GhcPs (LHsExpr GhcPs))
maybe_stmt <- String
-> Int -> String -> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
hscParseStmtWithLocation String
source Int
linenumber String
stmt
case Maybe (LStmt GhcPs (LHsExpr GhcPs))
maybe_stmt of
Maybe (LStmt GhcPs (LHsExpr GhcPs))
Nothing -> Maybe ([Id], ForeignHValue, FixityEnv)
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return Maybe ([Id], ForeignHValue, FixityEnv)
forall a. Maybe a
Nothing
Just LStmt GhcPs (LHsExpr GhcPs)
parsed_stmt -> do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv)))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> LStmt GhcPs (LHsExpr GhcPs)
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscParsedStmt HscEnv
hsc_env LStmt GhcPs (LHsExpr GhcPs)
parsed_stmt
hscParsedStmt :: HscEnv
-> GhciLStmt GhcPs
-> IO ( Maybe ([Id]
, ForeignHValue
, FixityEnv))
hscParsedStmt :: HscEnv
-> LStmt GhcPs (LHsExpr GhcPs)
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
hscParsedStmt HscEnv
hsc_env LStmt GhcPs (LHsExpr GhcPs)
stmt = HscEnv
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv)))
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
-> IO (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ do
([Id]
ids, LHsExpr GhcTc
tc_expr, FixityEnv
fix_env) <- IO
((WarningMessages, WarningMessages),
Maybe ([Id], LHsExpr GhcTc, FixityEnv))
-> Hsc ([Id], LHsExpr GhcTc, FixityEnv)
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO
((WarningMessages, WarningMessages),
Maybe ([Id], LHsExpr GhcTc, FixityEnv))
-> Hsc ([Id], LHsExpr GhcTc, FixityEnv))
-> IO
((WarningMessages, WarningMessages),
Maybe ([Id], LHsExpr GhcTc, FixityEnv))
-> Hsc ([Id], LHsExpr GhcTc, FixityEnv)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> LStmt GhcPs (LHsExpr GhcPs)
-> IO
((WarningMessages, WarningMessages),
Maybe ([Id], LHsExpr GhcTc, FixityEnv))
tcRnStmt HscEnv
hsc_env LStmt GhcPs (LHsExpr GhcPs)
stmt
CoreExpr
ds_expr <- IO ((WarningMessages, WarningMessages), Maybe CoreExpr)
-> Hsc CoreExpr
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe CoreExpr)
-> Hsc CoreExpr)
-> IO ((WarningMessages, WarningMessages), Maybe CoreExpr)
-> Hsc CoreExpr
forall a b. (a -> b) -> a -> b
$ HscEnv
-> LHsExpr GhcTc
-> IO ((WarningMessages, WarningMessages), Maybe CoreExpr)
deSugarExpr HscEnv
hsc_env LHsExpr GhcTc
tc_expr
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (String -> HscEnv -> CoreExpr -> IO ()
lintInteractiveExpr String
"desugar expression" HscEnv
hsc_env CoreExpr
ds_expr)
Hsc ()
handleWarnings
let src_span :: SrcSpan
src_span = SrcLoc -> SrcSpan
srcLocSpan SrcLoc
interactiveSrcLoc
ForeignHValue
hval <- IO ForeignHValue -> Hsc ForeignHValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ForeignHValue -> Hsc ForeignHValue)
-> IO ForeignHValue -> Hsc ForeignHValue
forall a b. (a -> b) -> a -> b
$ HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr HscEnv
hsc_env SrcSpan
src_span CoreExpr
ds_expr
Maybe ([Id], ForeignHValue, FixityEnv)
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return (Maybe ([Id], ForeignHValue, FixityEnv)
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv)))
-> Maybe ([Id], ForeignHValue, FixityEnv)
-> Hsc (Maybe ([Id], ForeignHValue, FixityEnv))
forall a b. (a -> b) -> a -> b
$ ([Id], ForeignHValue, FixityEnv)
-> Maybe ([Id], ForeignHValue, FixityEnv)
forall a. a -> Maybe a
Just ([Id]
ids, ForeignHValue
hval, FixityEnv
fix_env)
hscDecls :: HscEnv
-> String
-> IO ([TyThing], InteractiveContext)
hscDecls :: HscEnv -> String -> IO ([TyThing], InteractiveContext)
hscDecls HscEnv
hsc_env String
str = HscEnv
-> String -> String -> Int -> IO ([TyThing], InteractiveContext)
hscDeclsWithLocation HscEnv
hsc_env String
str String
"<interactive>" Int
1
hscParseDeclsWithLocation :: HscEnv -> String -> Int -> String -> IO [LHsDecl GhcPs]
hscParseDeclsWithLocation :: HscEnv -> String -> Int -> String -> IO [LHsDecl GhcPs]
hscParseDeclsWithLocation HscEnv
hsc_env String
source Int
line_num String
str = do
L SrcSpan
_ (HsModule{ hsmodDecls :: HsModule -> [LHsDecl GhcPs]
hsmodDecls = [LHsDecl GhcPs]
decls }) <-
HscEnv -> Hsc (Located HsModule) -> IO (Located HsModule)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (Located HsModule) -> IO (Located HsModule))
-> Hsc (Located HsModule) -> IO (Located HsModule)
forall a b. (a -> b) -> a -> b
$
String
-> Int -> P (Located HsModule) -> String -> Hsc (Located HsModule)
forall thing.
(Outputable thing, Data thing) =>
String -> Int -> P thing -> String -> Hsc thing
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data HsModule
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type Outputable HsModule
hscParseThingWithLocation String
source Int
line_num P (Located HsModule)
parseModule String
str
[LHsDecl GhcPs] -> IO [LHsDecl GhcPs]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return [LHsDecl GhcPs]
decls
hscDeclsWithLocation :: HscEnv
-> String
-> String
-> Int
-> IO ([TyThing], InteractiveContext)
hscDeclsWithLocation :: HscEnv
-> String -> String -> Int -> IO ([TyThing], InteractiveContext)
hscDeclsWithLocation HscEnv
hsc_env String
str String
source Int
linenumber = do
L SrcSpan
_ (HsModule{ hsmodDecls :: HsModule -> [LHsDecl GhcPs]
hsmodDecls = [LHsDecl GhcPs]
decls }) <-
HscEnv -> Hsc (Located HsModule) -> IO (Located HsModule)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (Located HsModule) -> IO (Located HsModule))
-> Hsc (Located HsModule) -> IO (Located HsModule)
forall a b. (a -> b) -> a -> b
$
String
-> Int -> P (Located HsModule) -> String -> Hsc (Located HsModule)
forall thing.
(Outputable thing, Data thing) =>
String -> Int -> P thing -> String -> Hsc thing
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data HsModule
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type Outputable HsModule
hscParseThingWithLocation String
source Int
linenumber P (Located HsModule)
parseModule String
str
HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
hscParsedDecls HscEnv
hsc_env [LHsDecl GhcPs]
decls
hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
hscParsedDecls HscEnv
hsc_env [LHsDecl GhcPs]
decls = HscEnv
-> Hsc ([TyThing], InteractiveContext)
-> IO ([TyThing], InteractiveContext)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc ([TyThing], InteractiveContext)
-> IO ([TyThing], InteractiveContext))
-> Hsc ([TyThing], InteractiveContext)
-> IO ([TyThing], InteractiveContext)
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
TcGblEnv
tc_gblenv <- IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv)
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
-> Hsc TcGblEnv
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [LHsDecl GhcPs]
-> IO ((WarningMessages, WarningMessages), Maybe TcGblEnv)
tcRnDeclsi HscEnv
hsc_env [LHsDecl GhcPs]
decls
let defaults :: Maybe [Type]
defaults = TcGblEnv -> Maybe [Type]
tcg_default TcGblEnv
tc_gblenv
let iNTERACTIVELoc :: ModLocation
iNTERACTIVELoc = ModLocation :: Maybe String -> String -> String -> String -> ModLocation
ModLocation{ ml_hs_file :: Maybe String
ml_hs_file = Maybe String
forall a. Maybe a
Nothing,
ml_hi_file :: String
ml_hi_file = String -> String
forall a. String -> a
panic String
"hsDeclsWithLocation:ml_hi_file",
ml_obj_file :: String
ml_obj_file = String -> String
forall a. String -> a
panic String
"hsDeclsWithLocation:ml_obj_file",
ml_hie_file :: String
ml_hie_file = String -> String
forall a. String -> a
panic String
"hsDeclsWithLocation:ml_hie_file" }
ModGuts
ds_result <- ModLocation -> TcGblEnv -> Hsc ModGuts
hscDesugar' ModLocation
iNTERACTIVELoc TcGblEnv
tc_gblenv
ModGuts
simpl_mg <- IO ModGuts -> Hsc ModGuts
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO ModGuts -> Hsc ModGuts) -> IO ModGuts -> Hsc ModGuts
forall a b. (a -> b) -> a -> b
$ do
[String]
plugins <- IORef [String] -> IO [String]
forall a. IORef a -> IO a
readIORef (TcGblEnv -> IORef [String]
tcg_th_coreplugins TcGblEnv
tc_gblenv)
HscEnv -> [String] -> ModGuts -> IO ModGuts
hscSimplify HscEnv
hsc_env [String]
plugins ModGuts
ds_result
(CgGuts
tidy_cg, ModDetails
mod_details) <- IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails))
-> IO (CgGuts, ModDetails) -> Hsc (CgGuts, ModDetails)
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModGuts -> IO (CgGuts, ModDetails)
tidyProgram HscEnv
hsc_env ModGuts
simpl_mg
let !CgGuts{ cg_module :: CgGuts -> Module
cg_module = Module
this_mod,
cg_binds :: CgGuts -> CoreProgram
cg_binds = CoreProgram
core_binds,
cg_tycons :: CgGuts -> [TyCon]
cg_tycons = [TyCon]
tycons,
cg_modBreaks :: CgGuts -> Maybe ModBreaks
cg_modBreaks = Maybe ModBreaks
mod_breaks } = CgGuts
tidy_cg
!ModDetails { md_insts :: ModDetails -> [ClsInst]
md_insts = [ClsInst]
cls_insts
, md_fam_insts :: ModDetails -> [FamInst]
md_fam_insts = [FamInst]
fam_insts } = ModDetails
mod_details
data_tycons :: [TyCon]
data_tycons = (TyCon -> IsSafeImport) -> [TyCon] -> [TyCon]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filter TyCon -> IsSafeImport
isDataTyCon [TyCon]
tycons
(CoreProgram
prepd_binds, Set CostCentre
_) <- {-# SCC "CorePrep" #-}
IO (CoreProgram, Set CostCentre)
-> Hsc (CoreProgram, Set CostCentre)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (CoreProgram, Set CostCentre)
-> Hsc (CoreProgram, Set CostCentre))
-> IO (CoreProgram, Set CostCentre)
-> Hsc (CoreProgram, Set CostCentre)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Module
-> ModLocation
-> CoreProgram
-> [TyCon]
-> IO (CoreProgram, Set CostCentre)
corePrepPgm HscEnv
hsc_env Module
this_mod ModLocation
iNTERACTIVELoc CoreProgram
core_binds [TyCon]
data_tycons
CompiledByteCode
cbc <- IO CompiledByteCode -> Hsc CompiledByteCode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO CompiledByteCode -> Hsc CompiledByteCode)
-> IO CompiledByteCode -> Hsc CompiledByteCode
forall a b. (a -> b) -> a -> b
$ HscEnv
-> Module
-> CoreProgram
-> [TyCon]
-> Maybe ModBreaks
-> IO CompiledByteCode
byteCodeGen HscEnv
hsc_env Module
this_mod
CoreProgram
prepd_binds [TyCon]
data_tycons Maybe ModBreaks
mod_breaks
let src_span :: SrcSpan
src_span = SrcLoc -> SrcSpan
srcLocSpan SrcLoc
interactiveSrcLoc
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ HscEnv -> SrcSpan -> CompiledByteCode -> IO ()
linkDecls HscEnv
hsc_env SrcSpan
src_span CompiledByteCode
cbc
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ HscEnv -> [SptEntry] -> IO ()
hscAddSptEntries HscEnv
hsc_env (CgGuts -> [SptEntry]
cg_spt_entries CgGuts
tidy_cg)
let tcs :: [TyCon]
tcs = (TyCon -> IsSafeImport) -> [TyCon] -> [TyCon]
forall a. (a -> IsSafeImport) -> [a] -> [a]
filterOut TyCon -> IsSafeImport
isImplicitTyCon (ModGuts -> [TyCon]
mg_tcs ModGuts
simpl_mg)
patsyns :: [PatSyn]
patsyns = ModGuts -> [PatSyn]
mg_patsyns ModGuts
simpl_mg
ext_ids :: [Id]
ext_ids = [ Id
id | Id
id <- CoreProgram -> [Id]
forall b. [Bind b] -> [b]
bindersOfBinds CoreProgram
core_binds
, Name -> IsSafeImport
isExternalName (Id -> Name
idName Id
id)
, IsSafeImport -> IsSafeImport
not (Id -> IsSafeImport
isDFunId Id
id IsSafeImport -> IsSafeImport -> IsSafeImport
|| Id -> IsSafeImport
isImplicitId Id
id) ]
new_tythings :: [TyThing]
new_tythings = (Id -> TyThing) -> [Id] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map Id -> TyThing
AnId [Id]
ext_ids [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ (TyCon -> TyThing) -> [TyCon] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map TyCon -> TyThing
ATyCon [TyCon]
tcs [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ (PatSyn -> TyThing) -> [PatSyn] -> [TyThing]
forall a b. (a -> b) -> [a] -> [b]
map (ConLike -> TyThing
AConLike (ConLike -> TyThing) -> (PatSyn -> ConLike) -> PatSyn -> TyThing
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PatSyn -> ConLike
PatSynCon) [PatSyn]
patsyns
ictxt :: InteractiveContext
ictxt = HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env
fix_env :: FixityEnv
fix_env = TcGblEnv -> FixityEnv
tcg_fix_env TcGblEnv
tc_gblenv
new_ictxt :: InteractiveContext
new_ictxt = InteractiveContext
-> [TyThing]
-> [ClsInst]
-> [FamInst]
-> Maybe [Type]
-> FixityEnv
-> InteractiveContext
extendInteractiveContext InteractiveContext
ictxt [TyThing]
new_tythings [ClsInst]
cls_insts
[FamInst]
fam_insts Maybe [Type]
defaults FixityEnv
fix_env
([TyThing], InteractiveContext)
-> Hsc ([TyThing], InteractiveContext)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ([TyThing]
new_tythings, InteractiveContext
new_ictxt)
hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
hscAddSptEntries HscEnv
hsc_env [SptEntry]
entries = do
let add_spt_entry :: SptEntry -> IO ()
add_spt_entry :: SptEntry -> IO ()
add_spt_entry (SptEntry Id
i Fingerprint
fpr) = do
ForeignHValue
val <- HscEnv -> Name -> IO ForeignHValue
getHValue HscEnv
hsc_env (Id -> Name
idName Id
i)
HscEnv -> Fingerprint -> ForeignHValue -> IO ()
addSptEntry HscEnv
hsc_env Fingerprint
fpr ForeignHValue
val
(SptEntry -> IO ()) -> [SptEntry] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type Monad IO
External instance of the constraint type Foldable []
mapM_ SptEntry -> IO ()
add_spt_entry [SptEntry]
entries
hscImport :: HscEnv -> String -> IO (ImportDecl GhcPs)
hscImport :: HscEnv -> String -> IO (ImportDecl GhcPs)
hscImport HscEnv
hsc_env String
str = HscEnv -> Hsc (ImportDecl GhcPs) -> IO (ImportDecl GhcPs)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (ImportDecl GhcPs) -> IO (ImportDecl GhcPs))
-> Hsc (ImportDecl GhcPs) -> IO (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ do
(L SrcSpan
_ (HsModule{hsmodImports :: HsModule -> [LImportDecl GhcPs]
hsmodImports=[LImportDecl GhcPs]
is})) <-
P (Located HsModule) -> String -> Hsc (Located HsModule)
forall thing.
(Outputable thing, Data thing) =>
P thing -> String -> Hsc thing
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data HsModule
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type Outputable HsModule
hscParseThing P (Located HsModule)
parseModule String
str
case [LImportDecl GhcPs]
is of
[L SrcSpan
_ ImportDecl GhcPs
i] -> ImportDecl GhcPs -> Hsc (ImportDecl GhcPs)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return ImportDecl GhcPs
i
[LImportDecl GhcPs]
_ -> IO (ImportDecl GhcPs) -> Hsc (ImportDecl GhcPs)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO (ImportDecl GhcPs) -> Hsc (ImportDecl GhcPs))
-> IO (ImportDecl GhcPs) -> Hsc (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$ ErrMsg -> IO (ImportDecl GhcPs)
forall (io :: * -> *) a. MonadIO io => ErrMsg -> io a
External instance of the constraint type MonadIO IO
throwOneError (ErrMsg -> IO (ImportDecl GhcPs))
-> ErrMsg -> IO (ImportDecl GhcPs)
forall a b. (a -> b) -> a -> b
$
DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) SrcSpan
noSrcSpan (SDoc -> ErrMsg) -> SDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"parse error in import declaration"
hscTcExpr :: HscEnv
-> TcRnExprMode
-> String
-> IO Type
hscTcExpr :: HscEnv -> TcRnExprMode -> String -> IO Type
hscTcExpr HscEnv
hsc_env0 TcRnExprMode
mode String
expr = HscEnv -> Hsc Type -> IO Type
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc Type -> IO Type) -> Hsc Type -> IO Type
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
LHsExpr GhcPs
parsed_expr <- String -> Hsc (LHsExpr GhcPs)
hscParseExpr String
expr
IO ((WarningMessages, WarningMessages), Maybe Type) -> Hsc Type
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe Type) -> Hsc Type)
-> IO ((WarningMessages, WarningMessages), Maybe Type) -> Hsc Type
forall a b. (a -> b) -> a -> b
$ HscEnv
-> TcRnExprMode
-> LHsExpr GhcPs
-> IO ((WarningMessages, WarningMessages), Maybe Type)
tcRnExpr HscEnv
hsc_env TcRnExprMode
mode LHsExpr GhcPs
parsed_expr
hscKcType
:: HscEnv
-> Bool
-> String
-> IO (Type, Kind)
hscKcType :: HscEnv -> IsSafeImport -> String -> IO (Type, Type)
hscKcType HscEnv
hsc_env0 IsSafeImport
normalise String
str = HscEnv -> Hsc (Type, Type) -> IO (Type, Type)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env0 (Hsc (Type, Type) -> IO (Type, Type))
-> Hsc (Type, Type) -> IO (Type, Type)
forall a b. (a -> b) -> a -> b
$ do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
LHsType GhcPs
ty <- String -> Hsc (LHsType GhcPs)
hscParseType String
str
IO ((WarningMessages, WarningMessages), Maybe (Type, Type))
-> Hsc (Type, Type)
forall a. IO ((WarningMessages, WarningMessages), Maybe a) -> Hsc a
ioMsgMaybe (IO ((WarningMessages, WarningMessages), Maybe (Type, Type))
-> Hsc (Type, Type))
-> IO ((WarningMessages, WarningMessages), Maybe (Type, Type))
-> Hsc (Type, Type)
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ZonkFlexi
-> IsSafeImport
-> LHsType GhcPs
-> IO ((WarningMessages, WarningMessages), Maybe (Type, Type))
tcRnType HscEnv
hsc_env ZonkFlexi
DefaultFlexi IsSafeImport
normalise LHsType GhcPs
ty
hscParseExpr :: String -> Hsc (LHsExpr GhcPs)
hscParseExpr :: String -> Hsc (LHsExpr GhcPs)
hscParseExpr String
expr = do
HscEnv
hsc_env <- Hsc HscEnv
getHscEnv
Maybe (LStmt GhcPs (LHsExpr GhcPs))
maybe_stmt <- String -> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
hscParseStmt String
expr
case Maybe (LStmt GhcPs (LHsExpr GhcPs))
maybe_stmt of
Just (L SrcSpan
_ (BodyStmt XBodyStmt GhcPs GhcPs (LHsExpr GhcPs)
_ LHsExpr GhcPs
expr SyntaxExpr GhcPs
_ SyntaxExpr GhcPs
_)) -> LHsExpr GhcPs -> Hsc (LHsExpr GhcPs)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return LHsExpr GhcPs
expr
Maybe (LStmt GhcPs (LHsExpr GhcPs))
_ -> ErrMsg -> Hsc (LHsExpr GhcPs)
forall (io :: * -> *) a. MonadIO io => ErrMsg -> io a
External instance of the constraint type MonadIO Hsc
throwOneError (ErrMsg -> Hsc (LHsExpr GhcPs)) -> ErrMsg -> Hsc (LHsExpr GhcPs)
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> SDoc -> ErrMsg
mkPlainErrMsg (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) SrcSpan
noSrcSpan
(String -> SDoc
text String
"not an expression:" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (String -> SDoc
text String
expr))
hscParseStmt :: String -> Hsc (Maybe (GhciLStmt GhcPs))
hscParseStmt :: String -> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
hscParseStmt = P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
-> String -> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
forall thing.
(Outputable thing, Data thing) =>
P thing -> String -> Hsc thing
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type forall body. Data body => Data (StmtLR GhcPs GhcPs body)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data (HsExpr GhcPs)
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (pl :: Pass) (pr :: Pass) body.
(OutputableBndrId pl, OutputableBndrId pr, Outputable body) =>
Outputable (StmtLR (GhcPass pl) (GhcPass pr) body)
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsExpr (GhcPass p))
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
hscParseThing P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt
hscParseStmtWithLocation :: String -> Int -> String
-> Hsc (Maybe (GhciLStmt GhcPs))
hscParseStmtWithLocation :: String
-> Int -> String -> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
hscParseStmtWithLocation String
source Int
linenumber String
stmt =
String
-> Int
-> P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
-> String
-> Hsc (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
forall thing.
(Outputable thing, Data thing) =>
String -> Int -> P thing -> String -> Hsc thing
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type forall body. Data body => Data (StmtLR GhcPs GhcPs body)
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data (HsExpr GhcPs)
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (pl :: Pass) (pr :: Pass) body.
(OutputableBndrId pl, OutputableBndrId pr, Outputable body) =>
Outputable (StmtLR (GhcPass pl) (GhcPass pr) body)
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsExpr (GhcPass p))
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
hscParseThingWithLocation String
source Int
linenumber P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt String
stmt
hscParseType :: String -> Hsc (LHsType GhcPs)
hscParseType :: String -> Hsc (LHsType GhcPs)
hscParseType = P (LHsType GhcPs) -> String -> Hsc (LHsType GhcPs)
forall thing.
(Outputable thing, Data thing) =>
P thing -> String -> Hsc thing
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data (HsType GhcPs)
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type forall (p :: Pass).
OutputableBndrId p =>
Outputable (HsType (GhcPass p))
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type OutputableBndr RdrName
External instance of the constraint type IsPass 'Parsed
hscParseThing P (LHsType GhcPs)
parseType
hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
hscParseIdentifier :: HscEnv -> String -> IO (Located RdrName)
hscParseIdentifier HscEnv
hsc_env String
str =
HscEnv -> Hsc (Located RdrName) -> IO (Located RdrName)
forall a. HscEnv -> Hsc a -> IO a
runInteractiveHsc HscEnv
hsc_env (Hsc (Located RdrName) -> IO (Located RdrName))
-> Hsc (Located RdrName) -> IO (Located RdrName)
forall a b. (a -> b) -> a -> b
$ P (Located RdrName) -> String -> Hsc (Located RdrName)
forall thing.
(Outputable thing, Data thing) =>
P thing -> String -> Hsc thing
External instance of the constraint type forall l e. (Data l, Data e) => Data (GenLocated l e)
External instance of the constraint type Data SrcSpan
External instance of the constraint type Data RdrName
External instance of the constraint type forall l e.
(Outputable l, Outputable e) =>
Outputable (GenLocated l e)
External instance of the constraint type Outputable SrcSpan
External instance of the constraint type Outputable RdrName
hscParseThing P (Located RdrName)
parseIdentifier String
str
hscParseThing :: (Outputable thing, Data thing)
=> Lexer.P thing -> String -> Hsc thing
hscParseThing :: P thing -> String -> Hsc thing
hscParseThing = String -> Int -> P thing -> String -> Hsc thing
forall thing.
(Outputable thing, Data thing) =>
String -> Int -> P thing -> String -> Hsc thing
Evidence bound by a type signature of the constraint type Data thing
Evidence bound by a type signature of the constraint type Outputable thing
hscParseThingWithLocation String
"<interactive>" Int
1
hscParseThingWithLocation :: (Outputable thing, Data thing) => String -> Int
-> Lexer.P thing -> String -> Hsc thing
hscParseThingWithLocation :: String -> Int -> P thing -> String -> Hsc thing
hscParseThingWithLocation String
source Int
linenumber P thing
parser String
str
= SDoc -> (thing -> ()) -> Hsc thing -> Hsc thing
forall (m :: * -> *) a.
(MonadIO m, HasDynFlags m) =>
SDoc -> (a -> ()) -> m a -> m a
External instance of the constraint type HasDynFlags Hsc
External instance of the constraint type MonadIO Hsc
withTimingD
(String -> SDoc
text String
"Parser [source]")
(() -> thing -> ()
forall a b. a -> b -> a
const ()) (Hsc thing -> Hsc thing) -> Hsc thing -> Hsc thing
forall a b. (a -> b) -> a -> b
$ {-# SCC "Parser" #-} do
DynFlags
dflags <- Hsc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
External instance of the constraint type HasDynFlags Hsc
getDynFlags
let buf :: StringBuffer
buf = String -> StringBuffer
stringToStringBuffer String
str
loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
fsLit String
source) Int
linenumber Int
1
case P thing -> PState -> ParseResult thing
forall a. P a -> PState -> ParseResult a
unP P thing
parser (DynFlags -> StringBuffer -> RealSrcLoc -> PState
mkPState DynFlags
dflags StringBuffer
buf RealSrcLoc
loc) of
PFailed PState
pst -> do
(WarningMessages, WarningMessages) -> Hsc thing
forall a. (WarningMessages, WarningMessages) -> Hsc a
handleWarningsThrowErrors (PState -> DynFlags -> (WarningMessages, WarningMessages)
getMessages PState
pst DynFlags
dflags)
POk PState
pst thing
thing -> do
(WarningMessages, WarningMessages) -> Hsc ()
logWarningsReportErrors (PState -> DynFlags -> (WarningMessages, WarningMessages)
getMessages PState
pst DynFlags
dflags)
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_parsed String
"Parser"
DumpFormat
FormatHaskell (thing -> SDoc
forall a. Outputable a => a -> SDoc
Evidence bound by a type signature of the constraint type Outputable thing
ppr thing
thing)
IO () -> Hsc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type MonadIO Hsc
liftIO (IO () -> Hsc ()) -> IO () -> Hsc ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn DynFlags
dflags DumpFlag
Opt_D_dump_parsed_ast String
"Parser AST"
DumpFormat
FormatHaskell (BlankSrcSpan -> thing -> SDoc
forall a. Data a => BlankSrcSpan -> a -> SDoc
Evidence bound by a type signature of the constraint type Data thing
showAstData BlankSrcSpan
NoBlankSrcSpan thing
thing)
thing -> Hsc thing
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Hsc
return thing
thing
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr HscEnv
hsc_env =
(Hooks
-> Maybe (HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue))
-> (HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue)
-> DynFlags
-> HscEnv
-> SrcSpan
-> CoreExpr
-> IO ForeignHValue
forall a. (Hooks -> Maybe a) -> a -> DynFlags -> a
lookupHook Hooks -> Maybe (HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue)
hscCompileCoreExprHook HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr' (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) HscEnv
hsc_env
hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr' :: HscEnv -> SrcSpan -> CoreExpr -> IO ForeignHValue
hscCompileCoreExpr' HscEnv
hsc_env SrcSpan
srcspan CoreExpr
ds_expr
= do { let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
; CoreExpr
simpl_expr <- HscEnv -> CoreExpr -> IO CoreExpr
simplifyExpr HscEnv
hsc_env CoreExpr
ds_expr
; let tidy_expr :: CoreExpr
tidy_expr = TidyEnv -> CoreExpr -> CoreExpr
tidyExpr TidyEnv
emptyTidyEnv CoreExpr
simpl_expr
; CoreExpr
prepd_expr <- DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
corePrepExpr DynFlags
dflags HscEnv
hsc_env CoreExpr
tidy_expr
; String -> HscEnv -> CoreExpr -> IO ()
lintInteractiveExpr String
"hscCompileExpr" HscEnv
hsc_env CoreExpr
prepd_expr
; UnlinkedBCO
bcos <- HscEnv -> Module -> CoreExpr -> IO UnlinkedBCO
coreExprToBCOs HscEnv
hsc_env
(InteractiveContext -> Module
icInteractiveModule (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env)) CoreExpr
prepd_expr
; ForeignHValue
hval <- HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue
linkExpr HscEnv
hsc_env SrcSpan
srcspan UnlinkedBCO
bcos
; ForeignHValue -> IO ForeignHValue
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ForeignHValue
hval }
dumpIfaceStats :: HscEnv -> IO ()
dumpIfaceStats :: HscEnv -> IO ()
dumpIfaceStats HscEnv
hsc_env = do
ExternalPackageState
eps <- IORef ExternalPackageState -> IO ExternalPackageState
forall a. IORef a -> IO a
readIORef (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env)
DynFlags -> IsSafeImport -> String -> SDoc -> IO ()
dumpIfSet DynFlags
dflags (IsSafeImport
dump_if_trace IsSafeImport -> IsSafeImport -> IsSafeImport
|| IsSafeImport
dump_rn_stats)
String
"Interface statistics"
(ExternalPackageState -> SDoc
ifaceStats ExternalPackageState
eps)
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
dump_rn_stats :: IsSafeImport
dump_rn_stats = DumpFlag -> DynFlags -> IsSafeImport
dopt DumpFlag
Opt_D_dump_rn_stats DynFlags
dflags
dump_if_trace :: IsSafeImport
dump_if_trace = DumpFlag -> DynFlags -> IsSafeImport
dopt DumpFlag
Opt_D_dump_if_trace DynFlags
dflags
showModuleIndex :: (Int, Int) -> String
showModuleIndex :: (Int, Int) -> String
showModuleIndex (Int
i,Int
n) = String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
padded String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n_str String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"] "
where
n_str :: String
n_str = Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
n
i_str :: String
i_str = Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
i
padded :: String
padded = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length String
n_str Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length String
i_str) Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
i_str