{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
module GHC.Driver.Backpack (doBackpack) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Backpack.Syntax
import GHC.Driver.Config
import GHC.Driver.Monad
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Driver.Main
import GHC.Driver.Make
import GHC.Driver.Env
import GHC.Driver.Errors
import GHC.Parser
import GHC.Parser.Header
import GHC.Parser.Lexer
import GHC.Parser.Annotation
import GHC.Parser.Errors.Ppr
import GHC hiding (Failed, Succeeded)
import GHC.Tc.Utils.Monad
import GHC.Iface.Recomp
import GHC.Builtin.Names
import GHC.Types.SrcLoc
import GHC.Types.SourceError
import GHC.Types.SourceText
import GHC.Types.SourceFile
import GHC.Types.Unique.FM
import GHC.Types.Unique.DFM
import GHC.Types.Unique.DSet
import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Panic
import GHC.Utils.Error
import GHC.Utils.Logger
import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.External
import GHC.Unit.State
import GHC.Unit.Finder
import GHC.Unit.Module.Graph
import GHC.Unit.Module.ModSummary
import GHC.Unit.Home.ModInfo
import GHC.Linker.Types
import qualified GHC.LanguageExtensions as LangExt
import GHC.Data.Maybe
import GHC.Data.StringBuffer
import GHC.Data.FastString
import qualified GHC.Data.EnumSet as EnumSet
import qualified GHC.Data.ShortText as ST
import Data.List ( partition )
import System.Exit
import Control.Monad
import System.FilePath
import Data.Version
import Data.IORef
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
doBackpack :: [FilePath] -> Ghc ()
doBackpack :: [FilePath] -> Ghc ()
doBackpack [FilePath
src_filename] = do
Logger
logger <- Ghc Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
DynFlags
dflags0 <- Ghc DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let dflags1 :: DynFlags
dflags1 = DynFlags
dflags0
[Located FilePath]
src_opts <- IO [Located FilePath] -> Ghc [Located FilePath]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Located FilePath] -> Ghc [Located FilePath])
-> IO [Located FilePath] -> Ghc [Located FilePath]
forall a b. (a -> b) -> a -> b
$ DynFlags -> FilePath -> IO [Located FilePath]
getOptionsFromFile DynFlags
dflags1 FilePath
src_filename
(DynFlags
dflags, [Located FilePath]
unhandled_flags, [Warn]
warns) <- IO (DynFlags, [Located FilePath], [Warn])
-> Ghc (DynFlags, [Located FilePath], [Warn])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (DynFlags, [Located FilePath], [Warn])
-> Ghc (DynFlags, [Located FilePath], [Warn]))
-> IO (DynFlags, [Located FilePath], [Warn])
-> Ghc (DynFlags, [Located FilePath], [Warn])
forall a b. (a -> b) -> a -> b
$ DynFlags
-> [Located FilePath] -> IO (DynFlags, [Located FilePath], [Warn])
forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located FilePath] -> m (DynFlags, [Located FilePath], [Warn])
parseDynamicFilePragma DynFlags
dflags1 [Located FilePath]
src_opts
(HscEnv -> HscEnv) -> Ghc ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession (\HscEnv
hsc_env -> HscEnv
hsc_env {hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags})
IO () -> Ghc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Ghc ()) -> IO () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ [Located FilePath] -> IO ()
forall (m :: * -> *). MonadIO m => [Located FilePath] -> m ()
checkProcessArgsResult [Located FilePath]
unhandled_flags
IO () -> Ghc ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Ghc ()) -> IO () -> Ghc ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> [Warn] -> IO ()
handleFlagWarnings Logger
logger DynFlags
dflags [Warn]
warns
StringBuffer
buf <- IO StringBuffer -> Ghc StringBuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StringBuffer -> Ghc StringBuffer)
-> IO StringBuffer -> Ghc StringBuffer
forall a b. (a -> b) -> a -> b
$ FilePath -> IO StringBuffer
hGetStringBuffer FilePath
src_filename
let loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
src_filename) Int
1 Int
1
case P [LHsUnit PackageName]
-> PState -> ParseResult [LHsUnit PackageName]
forall a. P a -> PState -> ParseResult a
unP P [LHsUnit PackageName]
parseBackpack (ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initParserState (DynFlags -> ParserOpts
initParserOpts DynFlags
dflags) StringBuffer
buf RealSrcLoc
loc) of
PFailed PState
pst -> ErrorMessages -> Ghc ()
forall (io :: * -> *) a. MonadIO io => ErrorMessages -> io a
throwErrors ((PsError -> MsgEnvelope DecoratedSDoc)
-> Bag PsError -> ErrorMessages
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PsError -> MsgEnvelope DecoratedSDoc
pprError (PState -> Bag PsError
getErrorMessages PState
pst))
POk PState
_ [LHsUnit PackageName]
pkgname_bkp -> do
HscEnv
hsc_env <- Ghc HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let bkp :: [LHsUnit HsComponentId]
bkp = UnitState
-> PackageNameMap HsComponentId
-> [LHsUnit PackageName]
-> [LHsUnit HsComponentId]
renameHsUnits (HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ([LHsUnit PackageName] -> PackageNameMap HsComponentId
bkpPackageNameMap [LHsUnit PackageName]
pkgname_bkp) [LHsUnit PackageName]
pkgname_bkp
FilePath -> [LHsUnit HsComponentId] -> BkpM () -> Ghc ()
forall a. FilePath -> [LHsUnit HsComponentId] -> BkpM a -> Ghc a
initBkpM FilePath
src_filename [LHsUnit HsComponentId]
bkp (BkpM () -> Ghc ()) -> BkpM () -> Ghc ()
forall a b. (a -> b) -> a -> b
$
[(Int, LHsUnit HsComponentId)]
-> ((Int, LHsUnit HsComponentId) -> BkpM ()) -> BkpM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int] -> [LHsUnit HsComponentId] -> [(Int, LHsUnit HsComponentId)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [LHsUnit HsComponentId]
bkp) (((Int, LHsUnit HsComponentId) -> BkpM ()) -> BkpM ())
-> ((Int, LHsUnit HsComponentId) -> BkpM ()) -> BkpM ()
forall a b. (a -> b) -> a -> b
$ \(Int
i, LHsUnit HsComponentId
lunit) -> do
let comp_name :: HsComponentId
comp_name = GenLocated SrcSpan HsComponentId -> HsComponentId
forall l e. GenLocated l e -> e
unLoc (HsUnit HsComponentId -> GenLocated SrcSpan HsComponentId
forall n. HsUnit n -> Located n
hsunitName (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
lunit))
(Int, Int) -> HsComponentId -> BkpM ()
msgTopPackage (Int
i,[LHsUnit HsComponentId] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LHsUnit HsComponentId]
bkp) HsComponentId
comp_name
BkpM () -> BkpM ()
forall a. BkpM a -> BkpM a
innerBkpM (BkpM () -> BkpM ()) -> BkpM () -> BkpM ()
forall a b. (a -> b) -> a -> b
$ do
let (IndefUnitId
cid, [(ModuleName, Module)]
insts) = LHsUnit HsComponentId -> (IndefUnitId, [(ModuleName, Module)])
computeUnitId LHsUnit HsComponentId
lunit
if [(ModuleName, Module)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, Module)]
insts
then if IndefUnitId
cid IndefUnitId -> IndefUnitId -> Bool
forall a. Eq a => a -> a -> Bool
== UnitId -> IndefUnitId
forall unit. unit -> Indefinite unit
Indefinite (FastString -> UnitId
UnitId (FilePath -> FastString
fsLit FilePath
"main"))
then LHsUnit HsComponentId -> BkpM ()
compileExe LHsUnit HsComponentId
lunit
else IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
compileUnit IndefUnitId
cid []
else IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
typecheckUnit IndefUnitId
cid [(ModuleName, Module)]
insts
doBackpack [FilePath]
_ =
GhcException -> Ghc ()
forall a. GhcException -> a
throwGhcException (FilePath -> GhcException
CmdLineError FilePath
"--backpack can only process a single file")
computeUnitId :: LHsUnit HsComponentId -> (IndefUnitId, [(ModuleName, Module)])
computeUnitId :: LHsUnit HsComponentId -> (IndefUnitId, [(ModuleName, Module)])
computeUnitId (L SrcSpan
_ HsUnit HsComponentId
unit) = (IndefUnitId
cid, [ (ModuleName
r, ModuleName -> Module
forall u. ModuleName -> GenModule (GenUnit u)
mkHoleModule ModuleName
r) | ModuleName
r <- [ModuleName]
reqs ])
where
cid :: IndefUnitId
cid = HsComponentId -> IndefUnitId
hsComponentId (GenLocated SrcSpan HsComponentId -> HsComponentId
forall l e. GenLocated l e -> e
unLoc (HsUnit HsComponentId -> GenLocated SrcSpan HsComponentId
forall n. HsUnit n -> Located n
hsunitName HsUnit HsComponentId
unit))
reqs :: [ModuleName]
reqs = UniqDSet ModuleName -> [ModuleName]
forall a. UniqDSet a -> [a]
uniqDSetToList ([UniqDSet ModuleName] -> UniqDSet ModuleName
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets ((GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> UniqDSet ModuleName)
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
-> [UniqDSet ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (HsUnitDecl HsComponentId -> UniqDSet ModuleName
get_reqs (HsUnitDecl HsComponentId -> UniqDSet ModuleName)
-> (GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> HsUnitDecl HsComponentId)
-> GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> UniqDSet ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> HsUnitDecl HsComponentId
forall l e. GenLocated l e -> e
unLoc) (HsUnit HsComponentId
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
forall n. HsUnit n -> [LHsUnitDecl n]
hsunitBody HsUnit HsComponentId
unit)))
get_reqs :: HsUnitDecl HsComponentId -> UniqDSet ModuleName
get_reqs (DeclD HscSource
HsigFile (L SrcSpan
_ ModuleName
modname) Maybe (Located HsModule)
_) = ModuleName -> UniqDSet ModuleName
forall a. Uniquable a => a -> UniqDSet a
unitUniqDSet ModuleName
modname
get_reqs (DeclD HscSource
HsSrcFile GenLocated SrcSpan ModuleName
_ Maybe (Located HsModule)
_) = UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
get_reqs (DeclD HscSource
HsBootFile GenLocated SrcSpan ModuleName
_ Maybe (Located HsModule)
_) = UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
get_reqs (IncludeD (IncludeDecl (L SrcSpan
_ HsUnitId HsComponentId
hsuid) Maybe [LRenaming]
_ Bool
_)) =
Unit -> UniqDSet ModuleName
forall u. GenUnit u -> UniqDSet ModuleName
unitFreeModuleHoles (HsUnitId HsComponentId -> Unit
convertHsComponentId HsUnitId HsComponentId
hsuid)
data SessionType
= ExeSession
| TcSession
| CompSession
deriving (SessionType -> SessionType -> Bool
(SessionType -> SessionType -> Bool)
-> (SessionType -> SessionType -> Bool) -> Eq SessionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SessionType -> SessionType -> Bool
$c/= :: SessionType -> SessionType -> Bool
== :: SessionType -> SessionType -> Bool
$c== :: SessionType -> SessionType -> Bool
Eq)
withBkpSession :: IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
withBkpSession :: forall a.
IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
withBkpSession IndefUnitId
cid [(ModuleName, Module)]
insts [(Unit, ModRenaming)]
deps SessionType
session_type BkpM a
do_this = do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let cid_fs :: FastString
cid_fs = UnitId -> FastString
forall u. IsUnitId u => u -> FastString
unitFS (IndefUnitId -> UnitId
forall unit. Indefinite unit -> unit
indefUnit IndefUnitId
cid)
is_primary :: Bool
is_primary = Bool
False
uid_str :: FilePath
uid_str = FastString -> FilePath
unpackFS (IndefUnitId -> [(ModuleName, Module)] -> FastString
forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> FastString
mkInstantiatedUnitHash IndefUnitId
cid [(ModuleName, Module)]
insts)
cid_str :: FilePath
cid_str = FastString -> FilePath
unpackFS FastString
cid_fs
key_base :: (DynFlags -> Maybe FilePath) -> FilePath
key_base DynFlags -> Maybe FilePath
p | Just FilePath
f <- DynFlags -> Maybe FilePath
p DynFlags
dflags = FilePath
f
| Bool
otherwise = FilePath
"."
sub_comp :: FilePath -> FilePath
sub_comp FilePath
p | Bool
is_primary = FilePath
p
| Bool
otherwise = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cid_str
outdir :: (DynFlags -> Maybe FilePath) -> FilePath
outdir DynFlags -> Maybe FilePath
p | SessionType
CompSession <- SessionType
session_type
, Bool -> Bool
not ([(ModuleName, Module)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, Module)]
insts) = FilePath -> FilePath
sub_comp ((DynFlags -> Maybe FilePath) -> FilePath
key_base DynFlags -> Maybe FilePath
p) FilePath -> FilePath -> FilePath
</> FilePath
uid_str
| Bool
otherwise = FilePath -> FilePath
sub_comp ((DynFlags -> Maybe FilePath) -> FilePath
key_base DynFlags -> Maybe FilePath
p)
mk_temp_env :: HscEnv -> HscEnv
mk_temp_env HscEnv
hsc_env = HscEnv
hsc_env
{ hsc_dflags :: DynFlags
hsc_dflags = UnitState -> DynFlags -> DynFlags
mk_temp_dflags (HscEnv -> UnitState
hsc_units HscEnv
hsc_env) (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
}
mk_temp_dflags :: UnitState -> DynFlags -> DynFlags
mk_temp_dflags UnitState
unit_state DynFlags
dflags = DynFlags
dflags
{ backend :: Backend
backend = case SessionType
session_type of
SessionType
TcSession -> Backend
NoBackend
SessionType
_ -> DynFlags -> Backend
backend DynFlags
dflags
, homeUnitInstantiations_ :: [(ModuleName, Module)]
homeUnitInstantiations_ = [(ModuleName, Module)]
insts
, homeUnitInstanceOf_ :: Maybe UnitId
homeUnitInstanceOf_ = if [(ModuleName, Module)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, Module)]
insts then Maybe UnitId
forall a. Maybe a
Nothing else UnitId -> Maybe UnitId
forall a. a -> Maybe a
Just (IndefUnitId -> UnitId
forall unit. Indefinite unit -> unit
indefUnit IndefUnitId
cid)
, homeUnitId_ :: UnitId
homeUnitId_ = case SessionType
session_type of
SessionType
TcSession -> IndefUnitId -> Maybe FastString -> UnitId
newUnitId IndefUnitId
cid Maybe FastString
forall a. Maybe a
Nothing
SessionType
_ | [(ModuleName, Module)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ModuleName, Module)]
insts -> IndefUnitId -> Maybe FastString -> UnitId
newUnitId IndefUnitId
cid Maybe FastString
forall a. Maybe a
Nothing
| Bool
otherwise -> IndefUnitId -> Maybe FastString -> UnitId
newUnitId IndefUnitId
cid (FastString -> Maybe FastString
forall a. a -> Maybe a
Just (IndefUnitId -> [(ModuleName, Module)] -> FastString
forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> FastString
mkInstantiatedUnitHash IndefUnitId
cid [(ModuleName, Module)]
insts))
, generalFlags :: EnumSet GeneralFlag
generalFlags = case SessionType
session_type of
SessionType
TcSession
| DynFlags -> Backend
backend DynFlags
dflags Backend -> Backend -> Bool
forall a. Eq a => a -> a -> Bool
/= Backend
NoBackend
-> GeneralFlag -> EnumSet GeneralFlag -> EnumSet GeneralFlag
forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert GeneralFlag
Opt_WriteInterface (DynFlags -> EnumSet GeneralFlag
generalFlags DynFlags
dflags)
SessionType
_ -> DynFlags -> EnumSet GeneralFlag
generalFlags DynFlags
dflags
, objectDir :: Maybe FilePath
objectDir = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just ((DynFlags -> Maybe FilePath) -> FilePath
outdir DynFlags -> Maybe FilePath
objectDir)
, hiDir :: Maybe FilePath
hiDir = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just ((DynFlags -> Maybe FilePath) -> FilePath
outdir DynFlags -> Maybe FilePath
hiDir)
, stubDir :: Maybe FilePath
stubDir = FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just ((DynFlags -> Maybe FilePath) -> FilePath
outdir DynFlags -> Maybe FilePath
stubDir)
, outputFile_ :: Maybe FilePath
outputFile_ = case SessionType
session_type of
SessionType
ExeSession -> DynFlags -> Maybe FilePath
outputFile_ DynFlags
dflags
SessionType
_ -> Maybe FilePath
forall a. Maybe a
Nothing
, dynOutputFile_ :: Maybe FilePath
dynOutputFile_ = case SessionType
session_type of
SessionType
ExeSession -> DynFlags -> Maybe FilePath
dynOutputFile_ DynFlags
dflags
SessionType
_ -> Maybe FilePath
forall a. Maybe a
Nothing
, importPaths :: [FilePath]
importPaths = []
, packageFlags :: [PackageFlag]
packageFlags = DynFlags -> [PackageFlag]
packageFlags DynFlags
dflags [PackageFlag] -> [PackageFlag] -> [PackageFlag]
forall a. [a] -> [a] -> [a]
++ ((Unit, ModRenaming) -> PackageFlag)
-> [(Unit, ModRenaming)] -> [PackageFlag]
forall a b. (a -> b) -> [a] -> [b]
map (\(Unit
uid0, ModRenaming
rn) ->
let uid :: Unit
uid = UnitState -> Unit -> Unit
unwireUnit UnitState
unit_state
(Unit -> Unit) -> Unit -> Unit
forall a b. (a -> b) -> a -> b
$ UnitState -> Unit -> Unit
improveUnit UnitState
unit_state
(Unit -> Unit) -> Unit -> Unit
forall a b. (a -> b) -> a -> b
$ UnitState -> ShHoleSubst -> Unit -> Unit
renameHoleUnit UnitState
unit_state ([(ModuleName, Module)] -> ShHoleSubst
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts) Unit
uid0
in FilePath -> PackageArg -> ModRenaming -> PackageFlag
ExposePackage
(DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags
(FilePath -> SDoc
text FilePath
"-unit-id" SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
uid SDoc -> SDoc -> SDoc
<+> ModRenaming -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModRenaming
rn))
(Unit -> PackageArg
UnitIdArg Unit
uid) ModRenaming
rn) [(Unit, ModRenaming)]
deps
}
(HscEnv -> HscEnv) -> BkpM a -> BkpM a
forall (m :: * -> *) a.
GhcMonad m =>
(HscEnv -> HscEnv) -> m a -> m a
withTempSession HscEnv -> HscEnv
mk_temp_env (BkpM a -> BkpM a) -> BkpM a -> BkpM a
forall a b. (a -> b) -> a -> b
$ do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
DynFlags -> BkpM ()
forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setSessionDynFlags DynFlags
dflags
BkpM a
do_this
withBkpExeSession :: [(Unit, ModRenaming)] -> BkpM a -> BkpM a
withBkpExeSession :: forall a. [(Unit, ModRenaming)] -> BkpM a -> BkpM a
withBkpExeSession [(Unit, ModRenaming)]
deps BkpM a
do_this =
IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
forall a.
IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
withBkpSession (UnitId -> IndefUnitId
forall unit. unit -> Indefinite unit
Indefinite (FastString -> UnitId
UnitId (FilePath -> FastString
fsLit FilePath
"main"))) [] [(Unit, ModRenaming)]
deps SessionType
ExeSession BkpM a
do_this
getSource :: IndefUnitId -> BkpM (LHsUnit HsComponentId)
getSource :: IndefUnitId -> BkpM (LHsUnit HsComponentId)
getSource IndefUnitId
cid = do
BkpEnv
bkp_env <- BkpM BkpEnv
getBkpEnv
case IndefUnitId
-> Map IndefUnitId (LHsUnit HsComponentId)
-> Maybe (LHsUnit HsComponentId)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup IndefUnitId
cid (BkpEnv -> Map IndefUnitId (LHsUnit HsComponentId)
bkp_table BkpEnv
bkp_env) of
Maybe (LHsUnit HsComponentId)
Nothing -> FilePath -> SDoc -> BkpM (LHsUnit HsComponentId)
forall a. HasCallStack => FilePath -> SDoc -> a
pprPanic FilePath
"missing needed dependency" (IndefUnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr IndefUnitId
cid)
Just LHsUnit HsComponentId
lunit -> LHsUnit HsComponentId -> BkpM (LHsUnit HsComponentId)
forall (m :: * -> *) a. Monad m => a -> m a
return LHsUnit HsComponentId
lunit
typecheckUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
typecheckUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
typecheckUnit IndefUnitId
cid [(ModuleName, Module)]
insts = do
LHsUnit HsComponentId
lunit <- IndefUnitId -> BkpM (LHsUnit HsComponentId)
getSource IndefUnitId
cid
SessionType
-> IndefUnitId
-> [(ModuleName, Module)]
-> LHsUnit HsComponentId
-> BkpM ()
buildUnit SessionType
TcSession IndefUnitId
cid [(ModuleName, Module)]
insts LHsUnit HsComponentId
lunit
compileUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
compileUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
compileUnit IndefUnitId
cid [(ModuleName, Module)]
insts = do
Unit -> BkpM ()
msgUnitId (IndefUnitId -> [(ModuleName, Module)] -> Unit
forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit IndefUnitId
cid [(ModuleName, Module)]
insts)
LHsUnit HsComponentId
lunit <- IndefUnitId -> BkpM (LHsUnit HsComponentId)
getSource IndefUnitId
cid
SessionType
-> IndefUnitId
-> [(ModuleName, Module)]
-> LHsUnit HsComponentId
-> BkpM ()
buildUnit SessionType
CompSession IndefUnitId
cid [(ModuleName, Module)]
insts LHsUnit HsComponentId
lunit
hsunitDeps :: Bool -> HsUnit HsComponentId -> [(Unit, ModRenaming)]
hsunitDeps :: Bool -> HsUnit HsComponentId -> [(Unit, ModRenaming)]
hsunitDeps Bool
include_sigs HsUnit HsComponentId
unit = (GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> [(Unit, ModRenaming)])
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
-> [(Unit, ModRenaming)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> [(Unit, ModRenaming)]
get_dep (HsUnit HsComponentId
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
forall n. HsUnit n -> [LHsUnitDecl n]
hsunitBody HsUnit HsComponentId
unit)
where
get_dep :: GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> [(Unit, ModRenaming)]
get_dep (L SrcSpan
_ (IncludeD (IncludeDecl (L SrcSpan
_ HsUnitId HsComponentId
hsuid) Maybe [LRenaming]
mb_lrn Bool
is_sig)))
| Bool
include_sigs Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
is_sig = [(HsUnitId HsComponentId -> Unit
convertHsComponentId HsUnitId HsComponentId
hsuid, Maybe [LRenaming] -> ModRenaming
forall {l}. Maybe [GenLocated l Renaming] -> ModRenaming
go Maybe [LRenaming]
mb_lrn)]
| Bool
otherwise = []
where
go :: Maybe [GenLocated l Renaming] -> ModRenaming
go Maybe [GenLocated l Renaming]
Nothing = Bool -> [(ModuleName, ModuleName)] -> ModRenaming
ModRenaming Bool
True []
go (Just [GenLocated l Renaming]
lrns) = Bool -> [(ModuleName, ModuleName)] -> ModRenaming
ModRenaming Bool
False ((GenLocated l Renaming -> (ModuleName, ModuleName))
-> [GenLocated l Renaming] -> [(ModuleName, ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated l Renaming -> (ModuleName, ModuleName)
forall {l}. GenLocated l Renaming -> (ModuleName, ModuleName)
convRn [GenLocated l Renaming]
lrns)
where
convRn :: GenLocated l Renaming -> (ModuleName, ModuleName)
convRn (L l
_ (Renaming (L SrcSpan
_ ModuleName
from) Maybe (GenLocated SrcSpan ModuleName)
Nothing)) = (ModuleName
from, ModuleName
from)
convRn (L l
_ (Renaming (L SrcSpan
_ ModuleName
from) (Just (L SrcSpan
_ ModuleName
to)))) = (ModuleName
from, ModuleName
to)
get_dep GenLocated SrcSpan (HsUnitDecl HsComponentId)
_ = []
buildUnit :: SessionType -> IndefUnitId -> [(ModuleName, Module)] -> LHsUnit HsComponentId -> BkpM ()
buildUnit :: SessionType
-> IndefUnitId
-> [(ModuleName, Module)]
-> LHsUnit HsComponentId
-> BkpM ()
buildUnit SessionType
session IndefUnitId
cid [(ModuleName, Module)]
insts LHsUnit HsComponentId
lunit = do
let deps_w_rns :: [(Unit, ModRenaming)]
deps_w_rns = Bool -> HsUnit HsComponentId -> [(Unit, ModRenaming)]
hsunitDeps (SessionType
session SessionType -> SessionType -> Bool
forall a. Eq a => a -> a -> Bool
== SessionType
TcSession) (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
lunit)
raw_deps :: [Unit]
raw_deps = ((Unit, ModRenaming) -> Unit) -> [(Unit, ModRenaming)] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (Unit, ModRenaming) -> Unit
forall a b. (a, b) -> a
fst [(Unit, ModRenaming)]
deps_w_rns
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let hsubst :: ShHoleSubst
hsubst = [(ModuleName, Module)] -> ShHoleSubst
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts
deps0 :: [Unit]
deps0 = (Unit -> Unit) -> [Unit] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (UnitState -> ShHoleSubst -> Unit -> Unit
renameHoleUnit (HscEnv -> UnitState
hsc_units HscEnv
hsc_env) ShHoleSubst
hsubst) [Unit]
raw_deps
[(Int, Unit)] -> ((Int, Unit) -> BkpM ()) -> BkpM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int] -> [Unit] -> [(Int, Unit)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [Unit]
deps0) (((Int, Unit) -> BkpM ()) -> BkpM ())
-> ((Int, Unit) -> BkpM ()) -> BkpM ()
forall a b. (a -> b) -> a -> b
$ \(Int
i, Unit
dep) ->
case SessionType
session of
SessionType
TcSession -> () -> BkpM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
SessionType
_ -> Int -> (Int, Unit) -> BkpM ()
compileInclude ([Unit] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Unit]
deps0) (Int
i, Unit
dep)
let deps :: [Unit]
deps = (Unit -> Unit) -> [Unit] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (UnitState -> Unit -> Unit
improveUnit (HscEnv -> UnitState
hsc_units HscEnv
hsc_env)) [Unit]
deps0
Maybe ExternalPackageState
mb_old_eps <- case SessionType
session of
SessionType
TcSession -> (ExternalPackageState -> Maybe ExternalPackageState)
-> IOEnv BkpEnv ExternalPackageState
-> IOEnv BkpEnv (Maybe ExternalPackageState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ExternalPackageState -> Maybe ExternalPackageState
forall a. a -> Maybe a
Just IOEnv BkpEnv ExternalPackageState
forall (m :: * -> *). GhcMonad m => m ExternalPackageState
getEpsGhc
SessionType
_ -> Maybe ExternalPackageState
-> IOEnv BkpEnv (Maybe ExternalPackageState)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ExternalPackageState
forall a. Maybe a
Nothing
GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
conf <- IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
forall a.
IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
withBkpSession IndefUnitId
cid [(ModuleName, Module)]
insts [(Unit, ModRenaming)]
deps_w_rns SessionType
session (BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module))
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
forall a b. (a -> b) -> a -> b
$ do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
ModuleGraph
mod_graph <- HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
lunit)
Messager
msg <- BkpM Messager
mkBackpackMsg
SuccessFlag
ok <- LoadHowMuch
-> Maybe Messager -> ModuleGraph -> IOEnv BkpEnv SuccessFlag
forall (m :: * -> *).
GhcMonad m =>
LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag
load' LoadHowMuch
LoadAllTargets (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
msg) ModuleGraph
mod_graph
Bool -> BkpM () -> BkpM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SuccessFlag -> Bool
failed SuccessFlag
ok) (IO () -> BkpM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BkpM ()) -> IO () -> BkpM ()
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1))
let hi_dir :: FilePath
hi_dir = FilePath -> Maybe FilePath -> FilePath
forall a. HasCallStack => FilePath -> Maybe a -> a
expectJust (FilePath -> FilePath
forall a. FilePath -> a
panic FilePath
"hiDir Backpack") (Maybe FilePath -> FilePath) -> Maybe FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ DynFlags -> Maybe FilePath
hiDir DynFlags
dflags
export_mod :: ModSummary -> (ModuleName, Module)
export_mod ModSummary
ms = (ModSummary -> ModuleName
ms_mod_name ModSummary
ms, ModSummary -> Module
ms_mod ModSummary
ms)
mods :: [(ModuleName, Module)]
mods = [ ModSummary -> (ModuleName, Module)
export_mod ModSummary
ms | ModSummary
ms <- ModuleGraph -> [ModSummary]
mgModSummaries ModuleGraph
mod_graph
, ModSummary -> HscSource
ms_hsc_src ModSummary
ms HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsSrcFile ]
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let home_mod_infos :: [HomeModInfo]
home_mod_infos = UniqDFM ModuleName HomeModInfo -> [HomeModInfo]
forall key elt. UniqDFM key elt -> [elt]
eltsUDFM (HscEnv -> UniqDFM ModuleName HomeModInfo
hsc_HPT HscEnv
hsc_env)
linkables :: [Linkable]
linkables = (HomeModInfo -> Linkable) -> [HomeModInfo] -> [Linkable]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Maybe Linkable -> Linkable
forall a. HasCallStack => FilePath -> Maybe a -> a
expectJust FilePath
"bkp link" (Maybe Linkable -> Linkable)
-> (HomeModInfo -> Maybe Linkable) -> HomeModInfo -> Linkable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> Maybe Linkable
hm_linkable)
([HomeModInfo] -> [Linkable])
-> ([HomeModInfo] -> [HomeModInfo]) -> [HomeModInfo] -> [Linkable]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HomeModInfo -> Bool) -> [HomeModInfo] -> [HomeModInfo]
forall a. (a -> Bool) -> [a] -> [a]
filter ((HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
==HscSource
HsSrcFile) (HscSource -> Bool)
-> (HomeModInfo -> HscSource) -> HomeModInfo -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ 'ModIfaceFinal -> HscSource
forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src (ModIface_ 'ModIfaceFinal -> HscSource)
-> (HomeModInfo -> ModIface_ 'ModIfaceFinal)
-> HomeModInfo
-> HscSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface)
([HomeModInfo] -> [Linkable]) -> [HomeModInfo] -> [Linkable]
forall a b. (a -> b) -> a -> b
$ [HomeModInfo]
home_mod_infos
getOfiles :: Linkable -> [FilePath]
getOfiles (LM UTCTime
_ Module
_ [Unlinked]
us) = (Unlinked -> FilePath) -> [Unlinked] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Unlinked -> FilePath
nameOfObject ((Unlinked -> Bool) -> [Unlinked] -> [Unlinked]
forall a. (a -> Bool) -> [a] -> [a]
filter Unlinked -> Bool
isObject [Unlinked]
us)
obj_files :: [FilePath]
obj_files = (Linkable -> [FilePath]) -> [Linkable] -> [FilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Linkable -> [FilePath]
getOfiles [Linkable]
linkables
state :: UnitState
state = HscEnv -> UnitState
hsc_units HscEnv
hsc_env
let compat_fs :: FastString
compat_fs = UnitId -> FastString
unitIdFS (IndefUnitId -> UnitId
forall unit. Indefinite unit -> unit
indefUnit IndefUnitId
cid)
compat_pn :: PackageName
compat_pn = FastString -> PackageName
PackageName FastString
compat_fs
unit_id :: UnitId
unit_id = GenHomeUnit UnitId -> UnitId
forall u. GenHomeUnit u -> UnitId
homeUnitId (HscEnv -> GenHomeUnit UnitId
hsc_home_unit HscEnv
hsc_env)
GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
-> BkpM
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
forall (m :: * -> *) a. Monad m => a -> m a
return GenericUnitInfo {
unitAbiHash :: ShortText
unitAbiHash = ShortText
"",
unitPackageId :: PackageId
unitPackageId = FastString -> PackageId
PackageId FastString
compat_fs,
unitPackageName :: PackageName
unitPackageName = PackageName
compat_pn,
unitPackageVersion :: Version
unitPackageVersion = [Int] -> Version
makeVersion [],
unitId :: UnitId
unitId = UnitId
unit_id,
unitComponentName :: Maybe PackageName
unitComponentName = Maybe PackageName
forall a. Maybe a
Nothing,
unitInstanceOf :: IndefUnitId
unitInstanceOf = IndefUnitId
cid,
unitInstantiations :: [(ModuleName, Module)]
unitInstantiations = [(ModuleName, Module)]
insts,
unitExposedModules :: [(ModuleName, Maybe Module)]
unitExposedModules = ((ModuleName, Module) -> (ModuleName, Maybe Module))
-> [(ModuleName, Module)] -> [(ModuleName, Maybe Module)]
forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
m,Module
n) -> (ModuleName
m,Module -> Maybe Module
forall a. a -> Maybe a
Just Module
n)) [(ModuleName, Module)]
mods,
unitHiddenModules :: [ModuleName]
unitHiddenModules = [],
unitDepends :: [UnitId]
unitDepends = case SessionType
session of
SessionType
TcSession -> []
SessionType
_ -> (Unit -> UnitId) -> [Unit] -> [UnitId]
forall a b. (a -> b) -> [a] -> [b]
map (Unit -> UnitId
toUnitId (Unit -> UnitId) -> (Unit -> Unit) -> Unit -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitState -> Unit -> Unit
unwireUnit UnitState
state)
([Unit] -> [UnitId]) -> [Unit] -> [UnitId]
forall a b. (a -> b) -> a -> b
$ [Unit]
deps [Unit] -> [Unit] -> [Unit]
forall a. [a] -> [a] -> [a]
++ [ Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
mod
| (ModuleName
_, Module
mod) <- [(ModuleName, Module)]
insts
, Bool -> Bool
not (Module -> Bool
forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
mod) ],
unitAbiDepends :: [(UnitId, ShortText)]
unitAbiDepends = [],
unitLinkerOptions :: [ShortText]
unitLinkerOptions = case SessionType
session of
SessionType
TcSession -> []
SessionType
_ -> (FilePath -> ShortText) -> [FilePath] -> [ShortText]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> ShortText
ST.pack ([FilePath] -> [ShortText]) -> [FilePath] -> [ShortText]
forall a b. (a -> b) -> a -> b
$ [FilePath]
obj_files,
unitImportDirs :: [ShortText]
unitImportDirs = [ FilePath -> ShortText
ST.pack (FilePath -> ShortText) -> FilePath -> ShortText
forall a b. (a -> b) -> a -> b
$ FilePath
hi_dir ],
unitIsExposed :: Bool
unitIsExposed = Bool
False,
unitIsIndefinite :: Bool
unitIsIndefinite = case SessionType
session of
SessionType
TcSession -> Bool
True
SessionType
_ -> Bool
False,
unitLibraries :: [ShortText]
unitLibraries = [],
unitExtDepLibsSys :: [ShortText]
unitExtDepLibsSys = [],
unitExtDepLibsGhc :: [ShortText]
unitExtDepLibsGhc = [],
unitLibraryDynDirs :: [ShortText]
unitLibraryDynDirs = [],
unitLibraryDirs :: [ShortText]
unitLibraryDirs = [],
unitExtDepFrameworks :: [ShortText]
unitExtDepFrameworks = [],
unitExtDepFrameworkDirs :: [ShortText]
unitExtDepFrameworkDirs = [],
unitCcOptions :: [ShortText]
unitCcOptions = [],
unitIncludes :: [ShortText]
unitIncludes = [],
unitIncludeDirs :: [ShortText]
unitIncludeDirs = [],
unitHaddockInterfaces :: [ShortText]
unitHaddockInterfaces = [],
unitHaddockHTMLs :: [ShortText]
unitHaddockHTMLs = [],
unitIsTrusted :: Bool
unitIsTrusted = Bool
False
}
GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
-> BkpM ()
forall (m :: * -> *).
GhcMonad m =>
GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
-> m ()
addUnit GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
conf
case Maybe ExternalPackageState
mb_old_eps of
Just ExternalPackageState
old_eps -> (ExternalPackageState -> ExternalPackageState) -> BkpM ()
forall (m :: * -> *).
GhcMonad m =>
(ExternalPackageState -> ExternalPackageState) -> m ()
updateEpsGhc_ (ExternalPackageState
-> ExternalPackageState -> ExternalPackageState
forall a b. a -> b -> a
const ExternalPackageState
old_eps)
Maybe ExternalPackageState
_ -> () -> BkpM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
compileExe :: LHsUnit HsComponentId -> BkpM ()
compileExe :: LHsUnit HsComponentId -> BkpM ()
compileExe LHsUnit HsComponentId
lunit = do
Unit -> BkpM ()
msgUnitId Unit
mainUnit
let deps_w_rns :: [(Unit, ModRenaming)]
deps_w_rns = Bool -> HsUnit HsComponentId -> [(Unit, ModRenaming)]
hsunitDeps Bool
False (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
lunit)
deps :: [Unit]
deps = ((Unit, ModRenaming) -> Unit) -> [(Unit, ModRenaming)] -> [Unit]
forall a b. (a -> b) -> [a] -> [b]
map (Unit, ModRenaming) -> Unit
forall a b. (a, b) -> a
fst [(Unit, ModRenaming)]
deps_w_rns
[(Int, Unit)] -> ((Int, Unit) -> BkpM ()) -> BkpM ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int] -> [Unit] -> [(Int, Unit)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [Unit]
deps) (((Int, Unit) -> BkpM ()) -> BkpM ())
-> ((Int, Unit) -> BkpM ()) -> BkpM ()
forall a b. (a -> b) -> a -> b
$ \(Int
i, Unit
dep) ->
Int -> (Int, Unit) -> BkpM ()
compileInclude ([Unit] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Unit]
deps) (Int
i, Unit
dep)
[(Unit, ModRenaming)] -> BkpM () -> BkpM ()
forall a. [(Unit, ModRenaming)] -> BkpM a -> BkpM a
withBkpExeSession [(Unit, ModRenaming)]
deps_w_rns (BkpM () -> BkpM ()) -> BkpM () -> BkpM ()
forall a b. (a -> b) -> a -> b
$ do
ModuleGraph
mod_graph <- HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
lunit)
Messager
msg <- BkpM Messager
mkBackpackMsg
SuccessFlag
ok <- LoadHowMuch
-> Maybe Messager -> ModuleGraph -> IOEnv BkpEnv SuccessFlag
forall (m :: * -> *).
GhcMonad m =>
LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag
load' LoadHowMuch
LoadAllTargets (Messager -> Maybe Messager
forall a. a -> Maybe a
Just Messager
msg) ModuleGraph
mod_graph
Bool -> BkpM () -> BkpM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SuccessFlag -> Bool
failed SuccessFlag
ok) (IO () -> BkpM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BkpM ()) -> IO () -> BkpM ()
forall a b. (a -> b) -> a -> b
$ ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1))
addUnit :: GhcMonad m => UnitInfo -> m ()
addUnit :: forall (m :: * -> *).
GhcMonad m =>
GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
-> m ()
addUnit GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
u = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
Logger
logger <- m Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
let dflags0 :: DynFlags
dflags0 = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
[UnitDatabase UnitId]
newdbs <- case HscEnv -> Maybe [UnitDatabase UnitId]
hsc_unit_dbs HscEnv
hsc_env of
Maybe [UnitDatabase UnitId]
Nothing -> FilePath -> m [UnitDatabase UnitId]
forall a. FilePath -> a
panic FilePath
"addUnit: called too early"
Just [UnitDatabase UnitId]
dbs ->
let newdb :: UnitDatabase UnitId
newdb = UnitDatabase
{ unitDatabasePath :: FilePath
unitDatabasePath = FilePath
"(in memory " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ DynFlags -> SDoc -> FilePath
showSDoc DynFlags
dflags0 (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr (GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
-> UnitId
forall compid srcpkgid srcpkgname uid modulename mod.
GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod
-> uid
unitId GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
u)) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")"
, unitDatabaseUnits :: [GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module]
unitDatabaseUnits = [GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
u]
}
in [UnitDatabase UnitId] -> m [UnitDatabase UnitId]
forall (m :: * -> *) a. Monad m => a -> m a
return ([UnitDatabase UnitId]
dbs [UnitDatabase UnitId]
-> [UnitDatabase UnitId] -> [UnitDatabase UnitId]
forall a. [a] -> [a] -> [a]
++ [UnitDatabase UnitId
newdb])
([UnitDatabase UnitId]
dbs,UnitState
unit_state,GenHomeUnit UnitId
home_unit,Maybe PlatformConstants
mconstants) <- IO
([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
-> m ([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
-> m ([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants))
-> IO
([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
-> m ([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
forall a b. (a -> b) -> a -> b
$ Logger
-> DynFlags
-> Maybe [UnitDatabase UnitId]
-> IO
([UnitDatabase UnitId], UnitState, GenHomeUnit UnitId,
Maybe PlatformConstants)
initUnits Logger
logger DynFlags
dflags0 ([UnitDatabase UnitId] -> Maybe [UnitDatabase UnitId]
forall a. a -> Maybe a
Just [UnitDatabase UnitId]
newdbs)
DynFlags
dflags <- IO DynFlags -> m DynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DynFlags -> m DynFlags) -> IO DynFlags -> m DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> Maybe PlatformConstants -> IO DynFlags
updatePlatformConstants DynFlags
dflags0 Maybe PlatformConstants
mconstants
let unit_env :: UnitEnv
unit_env = UnitEnv
{ ue_platform :: Platform
ue_platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
, ue_namever :: GhcNameVersion
ue_namever = DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags
, ue_home_unit :: GenHomeUnit UnitId
ue_home_unit = GenHomeUnit UnitId
home_unit
, ue_units :: UnitState
ue_units = UnitState
unit_state
}
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
setSession (HscEnv -> m ()) -> HscEnv -> m ()
forall a b. (a -> b) -> a -> b
$ HscEnv
hsc_env
{ hsc_unit_dbs :: Maybe [UnitDatabase UnitId]
hsc_unit_dbs = [UnitDatabase UnitId] -> Maybe [UnitDatabase UnitId]
forall a. a -> Maybe a
Just [UnitDatabase UnitId]
dbs
, hsc_dflags :: DynFlags
hsc_dflags = DynFlags
dflags
, hsc_unit_env :: UnitEnv
hsc_unit_env = UnitEnv
unit_env
}
compileInclude :: Int -> (Int, Unit) -> BkpM ()
compileInclude :: Int -> (Int, Unit) -> BkpM ()
compileInclude Int
n (Int
i, Unit
uid) = do
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let pkgs :: UnitState
pkgs = HscEnv -> UnitState
hsc_units HscEnv
hsc_env
(Int, Int) -> Unit -> BkpM ()
msgInclude (Int
i, Int
n) Unit
uid
case Unit
uid of
Unit
HoleUnit -> () -> BkpM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
RealUnit Definite UnitId
_ -> () -> BkpM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
VirtUnit GenInstantiatedUnit UnitId
i -> case UnitState
-> Unit
-> Maybe
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
lookupUnit UnitState
pkgs Unit
uid of
Maybe
(GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module)
Nothing -> BkpM () -> BkpM ()
forall a. BkpM a -> BkpM a
innerBkpM (BkpM () -> BkpM ()) -> BkpM () -> BkpM ()
forall a b. (a -> b) -> a -> b
$ IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
compileUnit (GenInstantiatedUnit UnitId -> IndefUnitId
forall unit. GenInstantiatedUnit unit -> Indefinite unit
instUnitInstanceOf GenInstantiatedUnit UnitId
i) (GenInstantiatedUnit UnitId -> [(ModuleName, Module)]
forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts GenInstantiatedUnit UnitId
i)
Just GenericUnitInfo
IndefUnitId PackageId PackageName UnitId ModuleName Module
_ -> () -> BkpM ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
type BkpM = IOEnv BkpEnv
data BkpEnv
= BkpEnv {
BkpEnv -> Session
bkp_session :: Session,
BkpEnv -> FilePath
bkp_filename :: FilePath,
BkpEnv -> Map IndefUnitId (LHsUnit HsComponentId)
bkp_table :: Map IndefUnitId (LHsUnit HsComponentId),
BkpEnv -> Int
bkp_level :: Int
}
instance {-# OVERLAPPING #-} HasDynFlags BkpM where
getDynFlags :: IOEnv BkpEnv DynFlags
getDynFlags = (HscEnv -> DynFlags)
-> IOEnv BkpEnv HscEnv -> IOEnv BkpEnv DynFlags
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HscEnv -> DynFlags
hsc_dflags IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
instance {-# OVERLAPPING #-} HasLogger BkpM where
getLogger :: BkpM Logger
getLogger = (HscEnv -> Logger) -> IOEnv BkpEnv HscEnv -> BkpM Logger
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HscEnv -> Logger
hsc_logger IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
instance GhcMonad BkpM where
getSession :: IOEnv BkpEnv HscEnv
getSession = do
Session IORef HscEnv
s <- (BkpEnv -> Session) -> BkpM BkpEnv -> IOEnv BkpEnv Session
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BkpEnv -> Session
bkp_session BkpM BkpEnv
forall env. IOEnv env env
getEnv
IORef HscEnv -> IOEnv BkpEnv HscEnv
forall a env. IORef a -> IOEnv env a
readMutVar IORef HscEnv
s
setSession :: HscEnv -> BkpM ()
setSession HscEnv
hsc_env = do
Session IORef HscEnv
s <- (BkpEnv -> Session) -> BkpM BkpEnv -> IOEnv BkpEnv Session
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BkpEnv -> Session
bkp_session BkpM BkpEnv
forall env. IOEnv env env
getEnv
IORef HscEnv -> HscEnv -> BkpM ()
forall a env. IORef a -> a -> IOEnv env ()
writeMutVar IORef HscEnv
s HscEnv
hsc_env
getBkpEnv :: BkpM BkpEnv
getBkpEnv :: BkpM BkpEnv
getBkpEnv = BkpM BkpEnv
forall env. IOEnv env env
getEnv
getBkpLevel :: BkpM Int
getBkpLevel :: BkpM Int
getBkpLevel = BkpEnv -> Int
bkp_level (BkpEnv -> Int) -> BkpM BkpEnv -> BkpM Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` BkpM BkpEnv
getBkpEnv
innerBkpM :: BkpM a -> BkpM a
innerBkpM :: forall a. BkpM a -> BkpM a
innerBkpM BkpM a
do_this =
(BkpEnv -> BkpEnv) -> BkpM a -> BkpM a
forall env env' a. (env -> env') -> IOEnv env' a -> IOEnv env a
updEnv (\BkpEnv
env -> BkpEnv
env { bkp_level :: Int
bkp_level = BkpEnv -> Int
bkp_level BkpEnv
env Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }) BkpM a
do_this
updateEpsGhc_ :: GhcMonad m => (ExternalPackageState -> ExternalPackageState) -> m ()
updateEpsGhc_ :: forall (m :: * -> *).
GhcMonad m =>
(ExternalPackageState -> ExternalPackageState) -> m ()
updateEpsGhc_ ExternalPackageState -> ExternalPackageState
f = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ IORef ExternalPackageState
-> (ExternalPackageState -> (ExternalPackageState, ())) -> IO ()
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env) (\ExternalPackageState
x -> (ExternalPackageState -> ExternalPackageState
f ExternalPackageState
x, ()))
getEpsGhc :: GhcMonad m => m ExternalPackageState
getEpsGhc :: forall (m :: * -> *). GhcMonad m => m ExternalPackageState
getEpsGhc = do
HscEnv
hsc_env <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
IO ExternalPackageState -> m ExternalPackageState
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ExternalPackageState -> m ExternalPackageState)
-> IO ExternalPackageState -> m ExternalPackageState
forall a b. (a -> b) -> a -> b
$ IORef ExternalPackageState -> IO ExternalPackageState
forall a. IORef a -> IO a
readIORef (HscEnv -> IORef ExternalPackageState
hsc_EPS HscEnv
hsc_env)
initBkpM :: FilePath -> [LHsUnit HsComponentId] -> BkpM a -> Ghc a
initBkpM :: forall a. FilePath -> [LHsUnit HsComponentId] -> BkpM a -> Ghc a
initBkpM FilePath
file [LHsUnit HsComponentId]
bkp BkpM a
m =
(Session -> IO a) -> Ghc a
forall a. (Session -> IO a) -> Ghc a
reifyGhc ((Session -> IO a) -> Ghc a) -> (Session -> IO a) -> Ghc a
forall a b. (a -> b) -> a -> b
$ \Session
session -> do
let env :: BkpEnv
env = BkpEnv {
bkp_session :: Session
bkp_session = Session
session,
bkp_table :: Map IndefUnitId (LHsUnit HsComponentId)
bkp_table = [(IndefUnitId, LHsUnit HsComponentId)]
-> Map IndefUnitId (LHsUnit HsComponentId)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(HsComponentId -> IndefUnitId
hsComponentId (GenLocated SrcSpan HsComponentId -> HsComponentId
forall l e. GenLocated l e -> e
unLoc (HsUnit HsComponentId -> GenLocated SrcSpan HsComponentId
forall n. HsUnit n -> Located n
hsunitName (LHsUnit HsComponentId -> HsUnit HsComponentId
forall l e. GenLocated l e -> e
unLoc LHsUnit HsComponentId
u))), LHsUnit HsComponentId
u) | LHsUnit HsComponentId
u <- [LHsUnit HsComponentId]
bkp],
bkp_filename :: FilePath
bkp_filename = FilePath
file,
bkp_level :: Int
bkp_level = Int
0
}
BkpEnv -> BkpM a -> IO a
forall env a. env -> IOEnv env a -> IO a
runIOEnv BkpEnv
env BkpM a
m
backpackProgressMsg :: Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg :: Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg Int
level Logger
logger DynFlags
dflags SDoc
msg =
Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath -> SDoc
text (Int -> Char -> FilePath
forall a. Int -> a -> [a]
replicate (Int
level Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2) Char
' ')
SDoc -> SDoc -> SDoc
<> SDoc
msg
mkBackpackMsg :: BkpM Messager
mkBackpackMsg :: BkpM Messager
mkBackpackMsg = do
Int
level <- BkpM Int
getBkpLevel
Messager -> BkpM Messager
forall (m :: * -> *) a. Monad m => a -> m a
return (Messager -> BkpM Messager) -> Messager -> BkpM Messager
forall a b. (a -> b) -> a -> b
$ \HscEnv
hsc_env (Int, Int)
mod_index RecompileRequired
recomp ModuleGraphNode
node ->
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
state :: UnitState
state = HscEnv -> UnitState
hsc_units HscEnv
hsc_env
showMsg :: SDoc -> SDoc -> IO ()
showMsg SDoc
msg SDoc
reason =
Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg Int
level Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
(Int, Int) -> SDoc
showModuleIndex (Int, Int)
mod_index SDoc -> SDoc -> SDoc
<>
SDoc
msg SDoc -> SDoc -> SDoc
<> DynFlags -> Bool -> ModuleGraphNode -> SDoc
showModMsg DynFlags
dflags (RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp) ModuleGraphNode
node
SDoc -> SDoc -> SDoc
<> SDoc
reason
in case ModuleGraphNode
node of
InstantiationNode GenInstantiatedUnit UnitId
_ ->
case RecompileRequired
recomp of
RecompileRequired
MustCompile -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Instantiating ") SDoc
empty
RecompileRequired
UpToDate
| DynFlags -> Int
verbosity (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Skipping ") SDoc
empty
| Bool
otherwise -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
RecompBecause FilePath
reason -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Instantiating ") (FilePath -> SDoc
text FilePath
" [" SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
reason SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
"]")
ModuleNode ExtendedModSummary
_ ->
case RecompileRequired
recomp of
RecompileRequired
MustCompile -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Compiling ") SDoc
empty
RecompileRequired
UpToDate
| DynFlags -> Int
verbosity (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Skipping ") SDoc
empty
| Bool
otherwise -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
RecompBecause FilePath
reason -> SDoc -> SDoc -> IO ()
showMsg (FilePath -> SDoc
text FilePath
"Compiling ") (FilePath -> SDoc
text FilePath
" [" SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
reason SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
"]")
backpackStyle :: PprStyle
backpackStyle :: PprStyle
backpackStyle =
PrintUnqualified -> Depth -> PprStyle
mkUserStyle
(QueryQualifyName
-> (Module -> Bool) -> QueryQualifyPackage -> PrintUnqualified
QueryQualify QueryQualifyName
neverQualifyNames
Module -> Bool
alwaysQualifyModules
QueryQualifyPackage
neverQualifyPackages) Depth
AllTheWay
msgTopPackage :: (Int,Int) -> HsComponentId -> BkpM ()
msgTopPackage :: (Int, Int) -> HsComponentId -> BkpM ()
msgTopPackage (Int
i,Int
n) (HsComponentId (PackageName FastString
fs_pn) IndefUnitId
_) = do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- BkpM Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
Int
level <- BkpM Int
getBkpLevel
IO () -> BkpM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BkpM ()) -> (SDoc -> IO ()) -> SDoc -> BkpM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg Int
level Logger
logger DynFlags
dflags
(SDoc -> BkpM ()) -> SDoc -> BkpM ()
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> SDoc
showModuleIndex (Int
i, Int
n) SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
"Processing " SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext FastString
fs_pn
msgUnitId :: Unit -> BkpM ()
msgUnitId :: Unit -> BkpM ()
msgUnitId Unit
pk = do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- BkpM Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
Int
level <- BkpM Int
getBkpLevel
let state :: UnitState
state = HscEnv -> UnitState
hsc_units HscEnv
hsc_env
IO () -> BkpM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BkpM ()) -> (SDoc -> IO ()) -> SDoc -> BkpM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg Int
level Logger
logger DynFlags
dflags
(SDoc -> BkpM ()) -> SDoc -> BkpM ()
forall a b. (a -> b) -> a -> b
$ UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state
(SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ FilePath -> SDoc
text FilePath
"Instantiating "
SDoc -> SDoc -> SDoc
<> PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
backpackStyle (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
pk)
msgInclude :: (Int,Int) -> Unit -> BkpM ()
msgInclude :: (Int, Int) -> Unit -> BkpM ()
msgInclude (Int
i,Int
n) Unit
uid = do
DynFlags
dflags <- IOEnv BkpEnv DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
Logger
logger <- BkpM Logger
forall (m :: * -> *). HasLogger m => m Logger
getLogger
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
Int
level <- BkpM Int
getBkpLevel
let state :: UnitState
state = HscEnv -> UnitState
hsc_units HscEnv
hsc_env
IO () -> BkpM ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> BkpM ()) -> (SDoc -> IO ()) -> SDoc -> BkpM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg Int
level Logger
logger DynFlags
dflags
(SDoc -> BkpM ()) -> SDoc -> BkpM ()
forall a b. (a -> b) -> a -> b
$ UnitState -> SDoc -> SDoc
pprWithUnitState UnitState
state
(SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> SDoc
showModuleIndex (Int
i, Int
n) SDoc -> SDoc -> SDoc
<> FilePath -> SDoc
text FilePath
"Including "
SDoc -> SDoc -> SDoc
<> PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
backpackStyle (Unit -> SDoc
forall a. Outputable a => a -> SDoc
ppr Unit
uid)
type PackageNameMap a = UniqFM PackageName a
unitDefines :: LHsUnit PackageName -> (PackageName, HsComponentId)
unitDefines :: LHsUnit PackageName -> (PackageName, HsComponentId)
unitDefines (L SrcSpan
_ HsUnit{ hsunitName :: forall n. HsUnit n -> Located n
hsunitName = L SrcSpan
_ pn :: PackageName
pn@(PackageName FastString
fs) })
= (PackageName
pn, PackageName -> IndefUnitId -> HsComponentId
HsComponentId PackageName
pn (UnitId -> IndefUnitId
forall unit. unit -> Indefinite unit
Indefinite (FastString -> UnitId
UnitId FastString
fs)))
bkpPackageNameMap :: [LHsUnit PackageName] -> PackageNameMap HsComponentId
bkpPackageNameMap :: [LHsUnit PackageName] -> PackageNameMap HsComponentId
bkpPackageNameMap [LHsUnit PackageName]
units = [(PackageName, HsComponentId)] -> PackageNameMap HsComponentId
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM ((LHsUnit PackageName -> (PackageName, HsComponentId))
-> [LHsUnit PackageName] -> [(PackageName, HsComponentId)]
forall a b. (a -> b) -> [a] -> [b]
map LHsUnit PackageName -> (PackageName, HsComponentId)
unitDefines [LHsUnit PackageName]
units)
renameHsUnits :: UnitState -> PackageNameMap HsComponentId -> [LHsUnit PackageName] -> [LHsUnit HsComponentId]
renameHsUnits :: UnitState
-> PackageNameMap HsComponentId
-> [LHsUnit PackageName]
-> [LHsUnit HsComponentId]
renameHsUnits UnitState
pkgstate PackageNameMap HsComponentId
m [LHsUnit PackageName]
units = (LHsUnit PackageName -> LHsUnit HsComponentId)
-> [LHsUnit PackageName] -> [LHsUnit HsComponentId]
forall a b. (a -> b) -> [a] -> [b]
map ((HsUnit PackageName -> HsUnit HsComponentId)
-> LHsUnit PackageName -> LHsUnit HsComponentId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsUnit PackageName -> HsUnit HsComponentId
renameHsUnit) [LHsUnit PackageName]
units
where
renamePackageName :: PackageName -> HsComponentId
renamePackageName :: PackageName -> HsComponentId
renamePackageName PackageName
pn =
case PackageNameMap HsComponentId -> PackageName -> Maybe HsComponentId
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM PackageNameMap HsComponentId
m PackageName
pn of
Maybe HsComponentId
Nothing ->
case UnitState -> PackageName -> Maybe IndefUnitId
lookupPackageName UnitState
pkgstate PackageName
pn of
Maybe IndefUnitId
Nothing -> FilePath -> HsComponentId
forall a. HasCallStack => FilePath -> a
error FilePath
"no package name"
Just IndefUnitId
cid -> PackageName -> IndefUnitId -> HsComponentId
HsComponentId PackageName
pn IndefUnitId
cid
Just HsComponentId
hscid -> HsComponentId
hscid
renameHsUnit :: HsUnit PackageName -> HsUnit HsComponentId
renameHsUnit :: HsUnit PackageName -> HsUnit HsComponentId
renameHsUnit HsUnit PackageName
u =
HsUnit {
hsunitName :: GenLocated SrcSpan HsComponentId
hsunitName = (PackageName -> HsComponentId)
-> GenLocated SrcSpan PackageName
-> GenLocated SrcSpan HsComponentId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PackageName -> HsComponentId
renamePackageName (HsUnit PackageName -> GenLocated SrcSpan PackageName
forall n. HsUnit n -> Located n
hsunitName HsUnit PackageName
u),
hsunitBody :: [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
hsunitBody = (GenLocated SrcSpan (HsUnitDecl PackageName)
-> GenLocated SrcSpan (HsUnitDecl HsComponentId))
-> [GenLocated SrcSpan (HsUnitDecl PackageName)]
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
forall a b. (a -> b) -> [a] -> [b]
map ((HsUnitDecl PackageName -> HsUnitDecl HsComponentId)
-> GenLocated SrcSpan (HsUnitDecl PackageName)
-> GenLocated SrcSpan (HsUnitDecl HsComponentId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsUnitDecl PackageName -> HsUnitDecl HsComponentId
renameHsUnitDecl) (HsUnit PackageName -> [GenLocated SrcSpan (HsUnitDecl PackageName)]
forall n. HsUnit n -> [LHsUnitDecl n]
hsunitBody HsUnit PackageName
u)
}
renameHsUnitDecl :: HsUnitDecl PackageName -> HsUnitDecl HsComponentId
renameHsUnitDecl :: HsUnitDecl PackageName -> HsUnitDecl HsComponentId
renameHsUnitDecl (DeclD HscSource
a GenLocated SrcSpan ModuleName
b Maybe (Located HsModule)
c) = HscSource
-> GenLocated SrcSpan ModuleName
-> Maybe (Located HsModule)
-> HsUnitDecl HsComponentId
forall n.
HscSource
-> GenLocated SrcSpan ModuleName
-> Maybe (Located HsModule)
-> HsUnitDecl n
DeclD HscSource
a GenLocated SrcSpan ModuleName
b Maybe (Located HsModule)
c
renameHsUnitDecl (IncludeD IncludeDecl PackageName
idecl) =
IncludeDecl HsComponentId -> HsUnitDecl HsComponentId
forall n. IncludeDecl n -> HsUnitDecl n
IncludeD IncludeDecl {
idUnitId :: GenLocated SrcSpan (HsUnitId HsComponentId)
idUnitId = (HsUnitId PackageName -> HsUnitId HsComponentId)
-> GenLocated SrcSpan (HsUnitId PackageName)
-> GenLocated SrcSpan (HsUnitId HsComponentId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsUnitId PackageName -> HsUnitId HsComponentId
renameHsUnitId (IncludeDecl PackageName
-> GenLocated SrcSpan (HsUnitId PackageName)
forall n. IncludeDecl n -> LHsUnitId n
idUnitId IncludeDecl PackageName
idecl),
idModRenaming :: Maybe [LRenaming]
idModRenaming = IncludeDecl PackageName -> Maybe [LRenaming]
forall n. IncludeDecl n -> Maybe [LRenaming]
idModRenaming IncludeDecl PackageName
idecl,
idSignatureInclude :: Bool
idSignatureInclude = IncludeDecl PackageName -> Bool
forall n. IncludeDecl n -> Bool
idSignatureInclude IncludeDecl PackageName
idecl
}
renameHsUnitId :: HsUnitId PackageName -> HsUnitId HsComponentId
renameHsUnitId :: HsUnitId PackageName -> HsUnitId HsComponentId
renameHsUnitId (HsUnitId GenLocated SrcSpan PackageName
ln [LHsModuleSubst PackageName]
subst)
= GenLocated SrcSpan HsComponentId
-> [LHsModuleSubst HsComponentId] -> HsUnitId HsComponentId
forall n. Located n -> [LHsModuleSubst n] -> HsUnitId n
HsUnitId ((PackageName -> HsComponentId)
-> GenLocated SrcSpan PackageName
-> GenLocated SrcSpan HsComponentId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PackageName -> HsComponentId
renamePackageName GenLocated SrcSpan PackageName
ln) ((LHsModuleSubst PackageName -> LHsModuleSubst HsComponentId)
-> [LHsModuleSubst PackageName] -> [LHsModuleSubst HsComponentId]
forall a b. (a -> b) -> [a] -> [b]
map ((HsModuleSubst PackageName -> HsModuleSubst HsComponentId)
-> LHsModuleSubst PackageName -> LHsModuleSubst HsComponentId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsModuleSubst PackageName -> HsModuleSubst HsComponentId
renameHsModuleSubst) [LHsModuleSubst PackageName]
subst)
renameHsModuleSubst :: HsModuleSubst PackageName -> HsModuleSubst HsComponentId
renameHsModuleSubst :: HsModuleSubst PackageName -> HsModuleSubst HsComponentId
renameHsModuleSubst (GenLocated SrcSpan ModuleName
lk, LHsModuleId PackageName
lm)
= (GenLocated SrcSpan ModuleName
lk, (HsModuleId PackageName -> HsModuleId HsComponentId)
-> LHsModuleId PackageName
-> GenLocated SrcSpan (HsModuleId HsComponentId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsModuleId PackageName -> HsModuleId HsComponentId
renameHsModuleId LHsModuleId PackageName
lm)
renameHsModuleId :: HsModuleId PackageName -> HsModuleId HsComponentId
renameHsModuleId :: HsModuleId PackageName -> HsModuleId HsComponentId
renameHsModuleId (HsModuleVar GenLocated SrcSpan ModuleName
lm) = GenLocated SrcSpan ModuleName -> HsModuleId HsComponentId
forall n. GenLocated SrcSpan ModuleName -> HsModuleId n
HsModuleVar GenLocated SrcSpan ModuleName
lm
renameHsModuleId (HsModuleId GenLocated SrcSpan (HsUnitId PackageName)
luid GenLocated SrcSpan ModuleName
lm) = GenLocated SrcSpan (HsUnitId HsComponentId)
-> GenLocated SrcSpan ModuleName -> HsModuleId HsComponentId
forall n.
LHsUnitId n -> GenLocated SrcSpan ModuleName -> HsModuleId n
HsModuleId ((HsUnitId PackageName -> HsUnitId HsComponentId)
-> GenLocated SrcSpan (HsUnitId PackageName)
-> GenLocated SrcSpan (HsUnitId HsComponentId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HsUnitId PackageName -> HsUnitId HsComponentId
renameHsUnitId GenLocated SrcSpan (HsUnitId PackageName)
luid) GenLocated SrcSpan ModuleName
lm
convertHsComponentId :: HsUnitId HsComponentId -> Unit
convertHsComponentId :: HsUnitId HsComponentId -> Unit
convertHsComponentId (HsUnitId (L SrcSpan
_ HsComponentId
hscid) [LHsModuleSubst HsComponentId]
subst)
= IndefUnitId -> [(ModuleName, Module)] -> Unit
forall u.
IsUnitId u =>
Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u
mkVirtUnit (HsComponentId -> IndefUnitId
hsComponentId HsComponentId
hscid) ((LHsModuleSubst HsComponentId -> (ModuleName, Module))
-> [LHsModuleSubst HsComponentId] -> [(ModuleName, Module)]
forall a b. (a -> b) -> [a] -> [b]
map (HsModuleSubst HsComponentId -> (ModuleName, Module)
convertHsModuleSubst (HsModuleSubst HsComponentId -> (ModuleName, Module))
-> (LHsModuleSubst HsComponentId -> HsModuleSubst HsComponentId)
-> LHsModuleSubst HsComponentId
-> (ModuleName, Module)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LHsModuleSubst HsComponentId -> HsModuleSubst HsComponentId
forall l e. GenLocated l e -> e
unLoc) [LHsModuleSubst HsComponentId]
subst)
convertHsModuleSubst :: HsModuleSubst HsComponentId -> (ModuleName, Module)
convertHsModuleSubst :: HsModuleSubst HsComponentId -> (ModuleName, Module)
convertHsModuleSubst (L SrcSpan
_ ModuleName
modname, L SrcSpan
_ HsModuleId HsComponentId
m) = (ModuleName
modname, HsModuleId HsComponentId -> Module
convertHsModuleId HsModuleId HsComponentId
m)
convertHsModuleId :: HsModuleId HsComponentId -> Module
convertHsModuleId :: HsModuleId HsComponentId -> Module
convertHsModuleId (HsModuleVar (L SrcSpan
_ ModuleName
modname)) = ModuleName -> Module
forall u. ModuleName -> GenModule (GenUnit u)
mkHoleModule ModuleName
modname
convertHsModuleId (HsModuleId (L SrcSpan
_ HsUnitId HsComponentId
hsuid) (L SrcSpan
_ ModuleName
modname)) = Unit -> ModuleName -> Module
forall u. u -> ModuleName -> GenModule u
mkModule (HsUnitId HsComponentId -> Unit
convertHsComponentId HsUnitId HsComponentId
hsuid) ModuleName
modname
hsunitModuleGraph :: HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph :: HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph HsUnit HsComponentId
unit = do
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let decls :: [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
decls = HsUnit HsComponentId
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
forall n. HsUnit n -> [LHsUnitDecl n]
hsunitBody HsUnit HsComponentId
unit
pn :: PackageName
pn = HsComponentId -> PackageName
hsPackageName (GenLocated SrcSpan HsComponentId -> HsComponentId
forall l e. GenLocated l e -> e
unLoc (HsUnit HsComponentId -> GenLocated SrcSpan HsComponentId
forall n. HsUnit n -> Located n
hsunitName HsUnit HsComponentId
unit))
home_unit :: GenHomeUnit UnitId
home_unit = HscEnv -> GenHomeUnit UnitId
hsc_home_unit HscEnv
hsc_env
let get_decl :: GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> IOEnv BkpEnv (Maybe ExtendedModSummary)
get_decl (L SrcSpan
_ (DeclD HscSource
hsc_src GenLocated SrcSpan ModuleName
lmodname Maybe (Located HsModule)
mb_hsmod)) =
ExtendedModSummary -> Maybe ExtendedModSummary
forall a. a -> Maybe a
Just (ExtendedModSummary -> Maybe ExtendedModSummary)
-> IOEnv BkpEnv ExtendedModSummary
-> IOEnv BkpEnv (Maybe ExtendedModSummary)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` PackageName
-> HscSource
-> GenLocated SrcSpan ModuleName
-> Maybe (Located HsModule)
-> IOEnv BkpEnv ExtendedModSummary
summariseDecl PackageName
pn HscSource
hsc_src GenLocated SrcSpan ModuleName
lmodname Maybe (Located HsModule)
mb_hsmod
get_decl GenLocated SrcSpan (HsUnitDecl HsComponentId)
_ = Maybe ExtendedModSummary -> IOEnv BkpEnv (Maybe ExtendedModSummary)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ExtendedModSummary
forall a. Maybe a
Nothing
[ExtendedModSummary]
nodes <- [Maybe ExtendedModSummary] -> [ExtendedModSummary]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe ExtendedModSummary] -> [ExtendedModSummary])
-> IOEnv BkpEnv [Maybe ExtendedModSummary]
-> IOEnv BkpEnv [ExtendedModSummary]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
-> IOEnv BkpEnv [Maybe ExtendedModSummary]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM GenLocated SrcSpan (HsUnitDecl HsComponentId)
-> IOEnv BkpEnv (Maybe ExtendedModSummary)
get_decl [GenLocated SrcSpan (HsUnitDecl HsComponentId)]
decls
let hsig_set :: Set ModuleName
hsig_set = [ModuleName] -> Set ModuleName
forall a. Ord a => [a] -> Set a
Set.fromList
[ ModSummary -> ModuleName
ms_mod_name ModSummary
ms
| ExtendedModSummary { emsModSummary :: ExtendedModSummary -> ModSummary
emsModSummary = ModSummary
ms } <- [ExtendedModSummary]
nodes
, ModSummary -> HscSource
ms_hsc_src ModSummary
ms HscSource -> HscSource -> Bool
forall a. Eq a => a -> a -> Bool
== HscSource
HsigFile
]
[ExtendedModSummary]
req_nodes <- ([Maybe ExtendedModSummary] -> [ExtendedModSummary])
-> IOEnv BkpEnv [Maybe ExtendedModSummary]
-> IOEnv BkpEnv [ExtendedModSummary]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe ExtendedModSummary] -> [ExtendedModSummary]
forall a. [Maybe a] -> [a]
catMaybes (IOEnv BkpEnv [Maybe ExtendedModSummary]
-> IOEnv BkpEnv [ExtendedModSummary])
-> (((ModuleName, Module)
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv [Maybe ExtendedModSummary])
-> ((ModuleName, Module)
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv [ExtendedModSummary]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ModuleName, Module)]
-> ((ModuleName, Module)
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv [Maybe ExtendedModSummary]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (GenHomeUnit UnitId -> [(ModuleName, Module)]
forall u. GenHomeUnit u -> GenInstantiations u
homeUnitInstantiations GenHomeUnit UnitId
home_unit) (((ModuleName, Module) -> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv [ExtendedModSummary])
-> ((ModuleName, Module)
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv [ExtendedModSummary]
forall a b. (a -> b) -> a -> b
$ \(ModuleName
mod_name, Module
_) ->
if ModuleName -> Set ModuleName -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member ModuleName
mod_name Set ModuleName
hsig_set
then Maybe ExtendedModSummary -> IOEnv BkpEnv (Maybe ExtendedModSummary)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ExtendedModSummary
forall a. Maybe a
Nothing
else (ModSummary -> Maybe ExtendedModSummary)
-> IOEnv BkpEnv ModSummary
-> IOEnv BkpEnv (Maybe ExtendedModSummary)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ExtendedModSummary -> Maybe ExtendedModSummary
forall a. a -> Maybe a
Just (ExtendedModSummary -> Maybe ExtendedModSummary)
-> (ModSummary -> ExtendedModSummary)
-> ModSummary
-> Maybe ExtendedModSummary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> ExtendedModSummary
extendModSummaryNoDeps) (IOEnv BkpEnv ModSummary
-> IOEnv BkpEnv (Maybe ExtendedModSummary))
-> IOEnv BkpEnv ModSummary
-> IOEnv BkpEnv (Maybe ExtendedModSummary)
forall a b. (a -> b) -> a -> b
$ PackageName -> ModuleName -> IOEnv BkpEnv ModSummary
summariseRequirement PackageName
pn ModuleName
mod_name
ModuleGraph -> BkpM ModuleGraph
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleGraph -> BkpM ModuleGraph)
-> ModuleGraph -> BkpM ModuleGraph
forall a b. (a -> b) -> a -> b
$ [ModuleGraphNode] -> ModuleGraph
mkModuleGraph' ([ModuleGraphNode] -> ModuleGraph)
-> [ModuleGraphNode] -> ModuleGraph
forall a b. (a -> b) -> a -> b
$
(ExtendedModSummary -> ModuleGraphNode
ModuleNode (ExtendedModSummary -> ModuleGraphNode)
-> [ExtendedModSummary] -> [ModuleGraphNode]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([ExtendedModSummary]
nodes [ExtendedModSummary]
-> [ExtendedModSummary] -> [ExtendedModSummary]
forall a. [a] -> [a] -> [a]
++ [ExtendedModSummary]
req_nodes)) [ModuleGraphNode] -> [ModuleGraphNode] -> [ModuleGraphNode]
forall a. [a] -> [a] -> [a]
++ UnitState -> [ModuleGraphNode]
instantiationNodes (HscEnv -> UnitState
hsc_units HscEnv
hsc_env)
summariseRequirement :: PackageName -> ModuleName -> BkpM ModSummary
summariseRequirement :: PackageName -> ModuleName -> IOEnv BkpEnv ModSummary
summariseRequirement PackageName
pn ModuleName
mod_name = do
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
let PackageName FastString
pn_fs = PackageName
pn
ModLocation
location <- IO ModLocation -> IOEnv BkpEnv ModLocation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModLocation -> IOEnv BkpEnv ModLocation)
-> IO ModLocation -> IOEnv BkpEnv ModLocation
forall a b. (a -> b) -> a -> b
$ DynFlags -> ModuleName -> FilePath -> FilePath -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
mod_name
(FastString -> FilePath
unpackFS FastString
pn_fs FilePath -> FilePath -> FilePath
</> ModuleName -> FilePath
moduleNameSlashes ModuleName
mod_name) FilePath
"hsig"
BkpEnv
env <- BkpM BkpEnv
getBkpEnv
UTCTime
time <- IO UTCTime -> IOEnv BkpEnv UTCTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UTCTime -> IOEnv BkpEnv UTCTime)
-> IO UTCTime -> IOEnv BkpEnv UTCTime
forall a b. (a -> b) -> a -> b
$ FilePath -> IO UTCTime
getModificationUTCTime (BkpEnv -> FilePath
bkp_filename BkpEnv
env)
Maybe UTCTime
hi_timestamp <- IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime))
-> IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Maybe UTCTime)
modificationTimeIfExists (ModLocation -> FilePath
ml_hi_file ModLocation
location)
Maybe UTCTime
hie_timestamp <- IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime))
-> IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Maybe UTCTime)
modificationTimeIfExists (ModLocation -> FilePath
ml_hie_file ModLocation
location)
let loc :: SrcSpan
loc = SrcLoc -> SrcSpan
srcLocSpan (FastString -> Int -> Int -> SrcLoc
mkSrcLoc (FilePath -> FastString
mkFastString (BkpEnv -> FilePath
bkp_filename BkpEnv
env)) Int
1 Int
1)
Module
mod <- IO Module -> IOEnv BkpEnv Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Module -> IOEnv BkpEnv Module)
-> IO Module -> IOEnv BkpEnv Module
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder HscEnv
hsc_env ModuleName
mod_name ModLocation
location
[(Maybe FastString, GenLocated SrcSpan ModuleName)]
extra_sig_imports <- IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv
BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)])
-> IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a b. (a -> b) -> a -> b
$ HscEnv
-> HscSource
-> ModuleName
-> IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
findExtraSigImports HscEnv
hsc_env HscSource
HsigFile ModuleName
mod_name
ModSummary -> IOEnv BkpEnv ModSummary
forall (m :: * -> *) a. Monad m => a -> m a
return ModSummary {
ms_mod :: Module
ms_mod = Module
mod,
ms_hsc_src :: HscSource
ms_hsc_src = HscSource
HsigFile,
ms_location :: ModLocation
ms_location = ModLocation
location,
ms_hs_date :: UTCTime
ms_hs_date = UTCTime
time,
ms_obj_date :: Maybe UTCTime
ms_obj_date = Maybe UTCTime
forall a. Maybe a
Nothing,
ms_iface_date :: Maybe UTCTime
ms_iface_date = Maybe UTCTime
hi_timestamp,
ms_hie_date :: Maybe UTCTime
ms_hie_date = Maybe UTCTime
hie_timestamp,
ms_srcimps :: [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_srcimps = [],
ms_textual_imps :: [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_textual_imps = [(Maybe FastString, GenLocated SrcSpan ModuleName)]
extra_sig_imports,
ms_parsed_mod :: Maybe HsParsedModule
ms_parsed_mod = HsParsedModule -> Maybe HsParsedModule
forall a. a -> Maybe a
Just (HsParsedModule {
hpm_module :: Located HsModule
hpm_module = SrcSpan -> HsModule -> Located HsModule
forall l e. l -> e -> GenLocated l e
L SrcSpan
loc (HsModule {
hsmodAnn :: EpAnn AnnsModule
hsmodAnn = EpAnn AnnsModule
forall a. EpAnn a
noAnn,
hsmodLayout :: LayoutInfo
hsmodLayout = LayoutInfo
NoLayoutInfo,
hsmodName :: Maybe (GenLocated (SrcAnn AnnListItem) ModuleName)
hsmodName = GenLocated (SrcAnn AnnListItem) ModuleName
-> Maybe (GenLocated (SrcAnn AnnListItem) ModuleName)
forall a. a -> Maybe a
Just (SrcAnn AnnListItem
-> ModuleName -> GenLocated (SrcAnn AnnListItem) ModuleName
forall l e. l -> e -> GenLocated l e
L (SrcSpan -> SrcAnn AnnListItem
forall ann. SrcSpan -> SrcAnn ann
noAnnSrcSpan SrcSpan
loc) ModuleName
mod_name),
hsmodExports :: Maybe (LocatedL [LIE GhcPs])
hsmodExports = Maybe (LocatedL [LIE GhcPs])
forall a. Maybe a
Nothing,
hsmodImports :: [LImportDecl GhcPs]
hsmodImports = [],
hsmodDecls :: [LHsDecl GhcPs]
hsmodDecls = [],
hsmodDeprecMessage :: Maybe (LocatedP WarningTxt)
hsmodDeprecMessage = Maybe (LocatedP WarningTxt)
forall a. Maybe a
Nothing,
hsmodHaddockModHeader :: Maybe LHsDocString
hsmodHaddockModHeader = Maybe LHsDocString
forall a. Maybe a
Nothing
}),
hpm_src_files :: [FilePath]
hpm_src_files = []
}),
ms_hspp_file :: FilePath
ms_hspp_file = FilePath
"",
ms_hspp_opts :: DynFlags
ms_hspp_opts = DynFlags
dflags,
ms_hspp_buf :: Maybe StringBuffer
ms_hspp_buf = Maybe StringBuffer
forall a. Maybe a
Nothing
}
summariseDecl :: PackageName
-> HscSource
-> Located ModuleName
-> Maybe (Located HsModule)
-> BkpM ExtendedModSummary
summariseDecl :: PackageName
-> HscSource
-> GenLocated SrcSpan ModuleName
-> Maybe (Located HsModule)
-> IOEnv BkpEnv ExtendedModSummary
summariseDecl PackageName
pn HscSource
hsc_src (L SrcSpan
_ ModuleName
modname) (Just Located HsModule
hsmod) = PackageName
-> HscSource
-> ModuleName
-> Located HsModule
-> IOEnv BkpEnv ExtendedModSummary
hsModuleToModSummary PackageName
pn HscSource
hsc_src ModuleName
modname Located HsModule
hsmod
summariseDecl PackageName
_pn HscSource
hsc_src lmodname :: GenLocated SrcSpan ModuleName
lmodname@(L SrcSpan
loc ModuleName
modname) Maybe (Located HsModule)
Nothing
= do HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
Maybe (Either ErrorMessages ExtendedModSummary)
r <- IO (Maybe (Either ErrorMessages ExtendedModSummary))
-> IOEnv BkpEnv (Maybe (Either ErrorMessages ExtendedModSummary))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Either ErrorMessages ExtendedModSummary))
-> IOEnv BkpEnv (Maybe (Either ErrorMessages ExtendedModSummary)))
-> IO (Maybe (Either ErrorMessages ExtendedModSummary))
-> IOEnv BkpEnv (Maybe (Either ErrorMessages ExtendedModSummary))
forall a b. (a -> b) -> a -> b
$ HscEnv
-> ModNodeMap ExtendedModSummary
-> IsBootInterface
-> GenLocated SrcSpan ModuleName
-> Bool
-> Maybe (StringBuffer, UTCTime)
-> [ModuleName]
-> IO (Maybe (Either ErrorMessages ExtendedModSummary))
summariseModule HscEnv
hsc_env
ModNodeMap ExtendedModSummary
forall a. ModNodeMap a
emptyModNodeMap
(HscSource -> IsBootInterface
hscSourceToIsBoot HscSource
hsc_src)
GenLocated SrcSpan ModuleName
lmodname
Bool
True
Maybe (StringBuffer, UTCTime)
forall a. Maybe a
Nothing
[]
case Maybe (Either ErrorMessages ExtendedModSummary)
r of
Maybe (Either ErrorMessages ExtendedModSummary)
Nothing -> MsgEnvelope DecoratedSDoc -> IOEnv BkpEnv ExtendedModSummary
forall (io :: * -> *) a.
MonadIO io =>
MsgEnvelope DecoratedSDoc -> io a
throwOneError (SrcSpan -> SDoc -> MsgEnvelope DecoratedSDoc
mkPlainMsgEnvelope SrcSpan
loc (FilePath -> SDoc
text FilePath
"module" SDoc -> SDoc -> SDoc
<+> ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
modname SDoc -> SDoc -> SDoc
<+> FilePath -> SDoc
text FilePath
"was not found"))
Just (Left ErrorMessages
err) -> ErrorMessages -> IOEnv BkpEnv ExtendedModSummary
forall (io :: * -> *) a. MonadIO io => ErrorMessages -> io a
throwErrors ErrorMessages
err
Just (Right ExtendedModSummary
summary) -> ExtendedModSummary -> IOEnv BkpEnv ExtendedModSummary
forall (m :: * -> *) a. Monad m => a -> m a
return ExtendedModSummary
summary
hsModuleToModSummary :: PackageName
-> HscSource
-> ModuleName
-> Located HsModule
-> BkpM ExtendedModSummary
hsModuleToModSummary :: PackageName
-> HscSource
-> ModuleName
-> Located HsModule
-> IOEnv BkpEnv ExtendedModSummary
hsModuleToModSummary PackageName
pn HscSource
hsc_src ModuleName
modname
Located HsModule
hsmod = do
let imps :: [LImportDecl GhcPs]
imps = HsModule -> [LImportDecl GhcPs]
hsmodImports (Located HsModule -> HsModule
forall l e. GenLocated l e -> e
unLoc Located HsModule
hsmod)
loc :: SrcSpan
loc = Located HsModule -> SrcSpan
forall l e. GenLocated l e -> l
getLoc Located HsModule
hsmod
HscEnv
hsc_env <- IOEnv BkpEnv HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
let PackageName FastString
unit_fs = PackageName
pn
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
ModLocation
location0 <- IO ModLocation -> IOEnv BkpEnv ModLocation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModLocation -> IOEnv BkpEnv ModLocation)
-> IO ModLocation -> IOEnv BkpEnv ModLocation
forall a b. (a -> b) -> a -> b
$ DynFlags -> ModuleName -> FilePath -> FilePath -> IO ModLocation
mkHomeModLocation2 DynFlags
dflags ModuleName
modname
(FastString -> FilePath
unpackFS FastString
unit_fs FilePath -> FilePath -> FilePath
</>
ModuleName -> FilePath
moduleNameSlashes ModuleName
modname)
(case HscSource
hsc_src of
HscSource
HsigFile -> FilePath
"hsig"
HscSource
HsBootFile -> FilePath
"hs-boot"
HscSource
HsSrcFile -> FilePath
"hs")
let location :: ModLocation
location = case HscSource
hsc_src of
HscSource
HsBootFile -> ModLocation -> ModLocation
addBootSuffixLocnOut ModLocation
location0
HscSource
_ -> ModLocation
location0
BkpEnv
env <- BkpM BkpEnv
getBkpEnv
UTCTime
time <- IO UTCTime -> IOEnv BkpEnv UTCTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UTCTime -> IOEnv BkpEnv UTCTime)
-> IO UTCTime -> IOEnv BkpEnv UTCTime
forall a b. (a -> b) -> a -> b
$ FilePath -> IO UTCTime
getModificationUTCTime (BkpEnv -> FilePath
bkp_filename BkpEnv
env)
Maybe UTCTime
hi_timestamp <- IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime))
-> IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Maybe UTCTime)
modificationTimeIfExists (ModLocation -> FilePath
ml_hi_file ModLocation
location)
Maybe UTCTime
hie_timestamp <- IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime))
-> IO (Maybe UTCTime) -> IOEnv BkpEnv (Maybe UTCTime)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO (Maybe UTCTime)
modificationTimeIfExists (ModLocation -> FilePath
ml_hie_file ModLocation
location)
let ([GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
src_idecls, [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
ord_idecls) = (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs) -> Bool)
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> ([GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)],
[GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((IsBootInterface -> IsBootInterface -> Bool
forall a. Eq a => a -> a -> Bool
== IsBootInterface
IsBoot) (IsBootInterface -> Bool)
-> (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> IsBootInterface)
-> GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportDecl GhcPs -> IsBootInterface
forall pass. ImportDecl pass -> IsBootInterface
ideclSource (ImportDecl GhcPs -> IsBootInterface)
-> (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ImportDecl GhcPs)
-> GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> IsBootInterface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ImportDecl GhcPs
forall l e. GenLocated l e -> e
unLoc) [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
[LImportDecl GhcPs]
imps
ordinary_imps :: [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
ordinary_imps = (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs) -> Bool)
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
/= Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
gHC_PRIM) (ModuleName -> Bool)
-> (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ModuleName)
-> GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated (SrcAnn AnnListItem) ModuleName -> ModuleName
forall l e. GenLocated l e -> e
unLoc (GenLocated (SrcAnn AnnListItem) ModuleName -> ModuleName)
-> (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> GenLocated (SrcAnn AnnListItem) ModuleName)
-> GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportDecl GhcPs -> GenLocated (SrcAnn AnnListItem) ModuleName
forall pass. ImportDecl pass -> XRec pass ModuleName
ideclName (ImportDecl GhcPs -> GenLocated (SrcAnn AnnListItem) ModuleName)
-> (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ImportDecl GhcPs)
-> GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> GenLocated (SrcAnn AnnListItem) ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> ImportDecl GhcPs
forall l e. GenLocated l e -> e
unLoc)
[GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
ord_idecls
implicit_prelude :: Bool
implicit_prelude = Extension -> DynFlags -> Bool
xopt Extension
LangExt.ImplicitPrelude DynFlags
dflags
implicit_imports :: [LImportDecl GhcPs]
implicit_imports = ModuleName
-> SrcSpan -> Bool -> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
mkPrelImports ModuleName
modname SrcSpan
loc
Bool
implicit_prelude [LImportDecl GhcPs]
imps
convImport :: GenLocated l (ImportDecl pass)
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
convImport (L l
_ ImportDecl pass
i) = ((StringLiteral -> FastString)
-> Maybe StringLiteral -> Maybe FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringLiteral -> FastString
sl_fs (ImportDecl pass -> Maybe StringLiteral
forall pass. ImportDecl pass -> Maybe StringLiteral
ideclPkgQual ImportDecl pass
i), GenLocated (SrcAnn a) ModuleName -> GenLocated SrcSpan ModuleName
forall a e. LocatedAn a e -> Located e
reLoc (GenLocated (SrcAnn a) ModuleName -> GenLocated SrcSpan ModuleName)
-> GenLocated (SrcAnn a) ModuleName
-> GenLocated SrcSpan ModuleName
forall a b. (a -> b) -> a -> b
$ ImportDecl pass -> XRec pass ModuleName
forall pass. ImportDecl pass -> XRec pass ModuleName
ideclName ImportDecl pass
i)
[(Maybe FastString, GenLocated SrcSpan ModuleName)]
extra_sig_imports <- IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv
BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)])
-> IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IOEnv BkpEnv [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a b. (a -> b) -> a -> b
$ HscEnv
-> HscSource
-> ModuleName
-> IO [(Maybe FastString, GenLocated SrcSpan ModuleName)]
findExtraSigImports HscEnv
hsc_env HscSource
hsc_src ModuleName
modname
let normal_imports :: [(Maybe FastString, GenLocated SrcSpan ModuleName)]
normal_imports = (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> (Maybe FastString, GenLocated SrcSpan ModuleName))
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
forall {pass} {a} {l}.
(XRec pass ModuleName ~ GenLocated (SrcAnn a) ModuleName) =>
GenLocated l (ImportDecl pass)
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
convImport ([GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
[LImportDecl GhcPs]
implicit_imports [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
forall a. [a] -> [a] -> [a]
++ [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
ordinary_imps)
([ModuleName]
implicit_sigs, [GenInstantiatedUnit UnitId]
inst_deps) <- IO ([ModuleName], [GenInstantiatedUnit UnitId])
-> IOEnv BkpEnv ([ModuleName], [GenInstantiatedUnit UnitId])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([ModuleName], [GenInstantiatedUnit UnitId])
-> IOEnv BkpEnv ([ModuleName], [GenInstantiatedUnit UnitId]))
-> IO ([ModuleName], [GenInstantiatedUnit UnitId])
-> IOEnv BkpEnv ([ModuleName], [GenInstantiatedUnit UnitId])
forall a b. (a -> b) -> a -> b
$ HscEnv
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> IO ([ModuleName], [GenInstantiatedUnit UnitId])
implicitRequirementsShallow HscEnv
hsc_env [(Maybe FastString, GenLocated SrcSpan ModuleName)]
normal_imports
Module
this_mod <- IO Module -> IOEnv BkpEnv Module
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Module -> IOEnv BkpEnv Module)
-> IO Module -> IOEnv BkpEnv Module
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModuleName -> ModLocation -> IO Module
addHomeModuleToFinder HscEnv
hsc_env ModuleName
modname ModLocation
location
ExtendedModSummary -> IOEnv BkpEnv ExtendedModSummary
forall (m :: * -> *) a. Monad m => a -> m a
return (ExtendedModSummary -> IOEnv BkpEnv ExtendedModSummary)
-> ExtendedModSummary -> IOEnv BkpEnv ExtendedModSummary
forall a b. (a -> b) -> a -> b
$ ExtendedModSummary
{ emsModSummary :: ModSummary
emsModSummary =
ModSummary {
ms_mod :: Module
ms_mod = Module
this_mod,
ms_hsc_src :: HscSource
ms_hsc_src = HscSource
hsc_src,
ms_location :: ModLocation
ms_location = ModLocation
location,
ms_hspp_file :: FilePath
ms_hspp_file = (case DynFlags -> Maybe FilePath
hiDir DynFlags
dflags of
Maybe FilePath
Nothing -> FilePath
""
Just FilePath
d -> FilePath
d) FilePath -> FilePath -> FilePath
</> FilePath
".." FilePath -> FilePath -> FilePath
</> ModuleName -> FilePath
moduleNameSlashes ModuleName
modname FilePath -> FilePath -> FilePath
<.> FilePath
"hi",
ms_hspp_opts :: DynFlags
ms_hspp_opts = DynFlags
dflags,
ms_hspp_buf :: Maybe StringBuffer
ms_hspp_buf = Maybe StringBuffer
forall a. Maybe a
Nothing,
ms_srcimps :: [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_srcimps = (GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> (Maybe FastString, GenLocated SrcSpan ModuleName))
-> [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
forall {pass} {a} {l}.
(XRec pass ModuleName ~ GenLocated (SrcAnn a) ModuleName) =>
GenLocated l (ImportDecl pass)
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
convImport [GenLocated (SrcAnn AnnListItem) (ImportDecl GhcPs)]
src_idecls,
ms_textual_imps :: [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_textual_imps = [(Maybe FastString, GenLocated SrcSpan ModuleName)]
normal_imports
[(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a. [a] -> [a] -> [a]
++ [(Maybe FastString, GenLocated SrcSpan ModuleName)]
extra_sig_imports
[(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall a. [a] -> [a] -> [a]
++ ((,) Maybe FastString
forall a. Maybe a
Nothing (GenLocated SrcSpan ModuleName
-> (Maybe FastString, GenLocated SrcSpan ModuleName))
-> (ModuleName -> GenLocated SrcSpan ModuleName)
-> ModuleName
-> (Maybe FastString, GenLocated SrcSpan ModuleName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> GenLocated SrcSpan ModuleName
forall e. e -> Located e
noLoc (ModuleName -> (Maybe FastString, GenLocated SrcSpan ModuleName))
-> [ModuleName]
-> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ModuleName]
implicit_sigs),
ms_parsed_mod :: Maybe HsParsedModule
ms_parsed_mod = HsParsedModule -> Maybe HsParsedModule
forall a. a -> Maybe a
Just (HsParsedModule {
hpm_module :: Located HsModule
hpm_module = Located HsModule
hsmod,
hpm_src_files :: [FilePath]
hpm_src_files = []
}),
ms_hs_date :: UTCTime
ms_hs_date = UTCTime
time,
ms_obj_date :: Maybe UTCTime
ms_obj_date = Maybe UTCTime
forall a. Maybe a
Nothing,
ms_iface_date :: Maybe UTCTime
ms_iface_date = Maybe UTCTime
hi_timestamp,
ms_hie_date :: Maybe UTCTime
ms_hie_date = Maybe UTCTime
hie_timestamp
}
, emsInstantiatedUnits :: [GenInstantiatedUnit UnitId]
emsInstantiatedUnits = [GenInstantiatedUnit UnitId]
inst_deps
}
newUnitId :: IndefUnitId -> Maybe FastString -> UnitId
newUnitId :: IndefUnitId -> Maybe FastString -> UnitId
newUnitId IndefUnitId
uid Maybe FastString
mhash = case Maybe FastString
mhash of
Maybe FastString
Nothing -> IndefUnitId -> UnitId
forall unit. Indefinite unit -> unit
indefUnit IndefUnitId
uid
Just FastString
hash -> FastString -> UnitId
UnitId (UnitId -> FastString
unitIdFS (IndefUnitId -> UnitId
forall unit. Indefinite unit -> unit
indefUnit IndefUnitId
uid) FastString -> FastString -> FastString
`appendFS` FilePath -> FastString
mkFastString FilePath
"+" FastString -> FastString -> FastString
`appendFS` FastString
hash)