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 [src_filename] = do
logger <- getLogger
dflags0 <- getDynFlags
let dflags1 = dflags0
src_opts <- liftIO $ getOptionsFromFile dflags1 src_filename
(dflags, unhandled_flags, warns) <- liftIO $ parseDynamicFilePragma dflags1 src_opts
modifySession (\hsc_env -> hsc_env {hsc_dflags = dflags})
liftIO $ checkProcessArgsResult unhandled_flags
liftIO $ handleFlagWarnings logger dflags warns
buf <- liftIO $ hGetStringBuffer src_filename
let loc = mkRealSrcLoc (mkFastString src_filename) 1 1
case unP parseBackpack (initParserState (initParserOpts dflags) buf loc) of
PFailed pst -> throwErrors (fmap pprError (getErrorMessages pst))
POk _ pkgname_bkp -> do
hsc_env <- getSession
let bkp = renameHsUnits (hsc_units hsc_env) (bkpPackageNameMap pkgname_bkp) pkgname_bkp
initBkpM src_filename bkp $
forM_ (zip [1..] bkp) $ \(i, lunit) -> do
let comp_name = unLoc (hsunitName (unLoc lunit))
msgTopPackage (i,length bkp) comp_name
innerBkpM $ do
let (cid, insts) = computeUnitId lunit
if null insts
then if cid == Indefinite (UnitId (fsLit "main"))
then compileExe lunit
else compileUnit cid []
else typecheckUnit cid insts
doBackpack _ =
throwGhcException (CmdLineError "--backpack can only process a single file")
computeUnitId :: LHsUnit HsComponentId -> (IndefUnitId, [(ModuleName, Module)])
computeUnitId (L _ unit) = (cid, [ (r, mkHoleModule r) | r <- reqs ])
where
cid = hsComponentId (unLoc (hsunitName unit))
reqs = uniqDSetToList (unionManyUniqDSets (map (get_reqs . unLoc) (hsunitBody unit)))
get_reqs (DeclD HsigFile (L _ modname) _) = unitUniqDSet modname
get_reqs (DeclD HsSrcFile _ _) = emptyUniqDSet
get_reqs (DeclD HsBootFile _ _) = emptyUniqDSet
get_reqs (IncludeD (IncludeDecl (L _ hsuid) _ _)) =
unitFreeModuleHoles (convertHsComponentId hsuid)
data SessionType
= ExeSession
| TcSession
| CompSession
deriving (Eq)
withBkpSession :: IndefUnitId
-> [(ModuleName, Module)]
-> [(Unit, ModRenaming)]
-> SessionType
-> BkpM a
-> BkpM a
withBkpSession cid insts deps session_type do_this = do
dflags <- getDynFlags
let cid_fs = unitFS (indefUnit cid)
is_primary = False
uid_str = unpackFS (mkInstantiatedUnitHash cid insts)
cid_str = unpackFS cid_fs
key_base p | Just f <- p dflags = f
| otherwise = "."
sub_comp p | is_primary = p
| otherwise = p </> cid_str
outdir p | CompSession <- session_type
, not (null insts) = sub_comp (key_base p) </> uid_str
| otherwise = sub_comp (key_base p)
mk_temp_env hsc_env = hsc_env
{ hsc_dflags = mk_temp_dflags (hsc_units hsc_env) (hsc_dflags hsc_env)
}
mk_temp_dflags unit_state dflags = dflags
{ backend = case session_type of
TcSession -> NoBackend
_ -> backend dflags
, homeUnitInstantiations_ = insts
, homeUnitInstanceOf_ = if null insts then Nothing else Just (indefUnit cid)
, homeUnitId_ = case session_type of
TcSession -> newUnitId cid Nothing
_ | null insts -> newUnitId cid Nothing
| otherwise -> newUnitId cid (Just (mkInstantiatedUnitHash cid insts))
, generalFlags = case session_type of
TcSession
| backend dflags /= NoBackend
-> EnumSet.insert Opt_WriteInterface (generalFlags dflags)
_ -> generalFlags dflags
, objectDir = Just (outdir objectDir)
, hiDir = Just (outdir hiDir)
, stubDir = Just (outdir stubDir)
, outputFile_ = case session_type of
ExeSession -> outputFile_ dflags
_ -> Nothing
, dynOutputFile_ = case session_type of
ExeSession -> dynOutputFile_ dflags
_ -> Nothing
, importPaths = []
, packageFlags = packageFlags dflags ++ map (\(uid0, rn) ->
let uid = unwireUnit unit_state
$ improveUnit unit_state
$ renameHoleUnit unit_state (listToUFM insts) uid0
in ExposePackage
(showSDoc dflags
(text "-unit-id" <+> ppr uid <+> ppr rn))
(UnitIdArg uid) rn) deps
}
withTempSession mk_temp_env $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
do_this
withBkpExeSession :: [(Unit, ModRenaming)] -> BkpM a -> BkpM a
withBkpExeSession deps do_this =
withBkpSession (Indefinite (UnitId (fsLit "main"))) [] deps ExeSession do_this
getSource :: IndefUnitId -> BkpM (LHsUnit HsComponentId)
getSource cid = do
bkp_env <- getBkpEnv
case Map.lookup cid (bkp_table bkp_env) of
Nothing -> pprPanic "missing needed dependency" (ppr cid)
Just lunit -> return lunit
typecheckUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
typecheckUnit cid insts = do
lunit <- getSource cid
buildUnit TcSession cid insts lunit
compileUnit :: IndefUnitId -> [(ModuleName, Module)] -> BkpM ()
compileUnit cid insts = do
msgUnitId (mkVirtUnit cid insts)
lunit <- getSource cid
buildUnit CompSession cid insts lunit
hsunitDeps :: Bool -> HsUnit HsComponentId -> [(Unit, ModRenaming)]
hsunitDeps include_sigs unit = concatMap get_dep (hsunitBody unit)
where
get_dep (L _ (IncludeD (IncludeDecl (L _ hsuid) mb_lrn is_sig)))
| include_sigs || not is_sig = [(convertHsComponentId hsuid, go mb_lrn)]
| otherwise = []
where
go Nothing = ModRenaming True []
go (Just lrns) = ModRenaming False (map convRn lrns)
where
convRn (L _ (Renaming (L _ from) Nothing)) = (from, from)
convRn (L _ (Renaming (L _ from) (Just (L _ to)))) = (from, to)
get_dep _ = []
buildUnit :: SessionType -> IndefUnitId -> [(ModuleName, Module)] -> LHsUnit HsComponentId -> BkpM ()
buildUnit session cid insts lunit = do
let deps_w_rns = hsunitDeps (session == TcSession) (unLoc lunit)
raw_deps = map fst deps_w_rns
hsc_env <- getSession
let hsubst = listToUFM insts
deps0 = map (renameHoleUnit (hsc_units hsc_env) hsubst) raw_deps
forM_ (zip [1..] deps0) $ \(i, dep) ->
case session of
TcSession -> return ()
_ -> compileInclude (length deps0) (i, dep)
let deps = map (improveUnit (hsc_units hsc_env)) deps0
mb_old_eps <- case session of
TcSession -> fmap Just getEpsGhc
_ -> return Nothing
conf <- withBkpSession cid insts deps_w_rns session $ do
dflags <- getDynFlags
mod_graph <- hsunitModuleGraph (unLoc lunit)
msg <- mkBackpackMsg
ok <- load' LoadAllTargets (Just msg) mod_graph
when (failed ok) (liftIO $ exitWith (ExitFailure 1))
let hi_dir = expectJust (panic "hiDir Backpack") $ hiDir dflags
export_mod ms = (ms_mod_name ms, ms_mod ms)
mods = [ export_mod ms | ms <- mgModSummaries mod_graph
, ms_hsc_src ms == HsSrcFile ]
hsc_env <- getSession
let home_mod_infos = eltsUDFM (hsc_HPT hsc_env)
linkables = map (expectJust "bkp link" . hm_linkable)
. filter ((==HsSrcFile) . mi_hsc_src . hm_iface)
$ home_mod_infos
getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
obj_files = concatMap getOfiles linkables
state = hsc_units hsc_env
let compat_fs = unitIdFS (indefUnit cid)
compat_pn = PackageName compat_fs
unit_id = homeUnitId (hsc_home_unit hsc_env)
return GenericUnitInfo {
unitAbiHash = "",
unitPackageId = PackageId compat_fs,
unitPackageName = compat_pn,
unitPackageVersion = makeVersion [],
unitId = unit_id,
unitComponentName = Nothing,
unitInstanceOf = cid,
unitInstantiations = insts,
unitExposedModules = map (\(m,n) -> (m,Just n)) mods,
unitHiddenModules = [],
unitDepends = case session of
TcSession -> []
_ -> map (toUnitId . unwireUnit state)
$ deps ++ [ moduleUnit mod
| (_, mod) <- insts
, not (isHoleModule mod) ],
unitAbiDepends = [],
unitLinkerOptions = case session of
TcSession -> []
_ -> map ST.pack $ obj_files,
unitImportDirs = [ ST.pack $ hi_dir ],
unitIsExposed = False,
unitIsIndefinite = case session of
TcSession -> True
_ -> False,
unitLibraries = [],
unitExtDepLibsSys = [],
unitExtDepLibsGhc = [],
unitLibraryDynDirs = [],
unitLibraryDirs = [],
unitExtDepFrameworks = [],
unitExtDepFrameworkDirs = [],
unitCcOptions = [],
unitIncludes = [],
unitIncludeDirs = [],
unitHaddockInterfaces = [],
unitHaddockHTMLs = [],
unitIsTrusted = False
}
addUnit conf
case mb_old_eps of
Just old_eps -> updateEpsGhc_ (const old_eps)
_ -> return ()
compileExe :: LHsUnit HsComponentId -> BkpM ()
compileExe lunit = do
msgUnitId mainUnit
let deps_w_rns = hsunitDeps False (unLoc lunit)
deps = map fst deps_w_rns
forM_ (zip [1..] deps) $ \(i, dep) ->
compileInclude (length deps) (i, dep)
withBkpExeSession deps_w_rns $ do
mod_graph <- hsunitModuleGraph (unLoc lunit)
msg <- mkBackpackMsg
ok <- load' LoadAllTargets (Just msg) mod_graph
when (failed ok) (liftIO $ exitWith (ExitFailure 1))
addUnit :: GhcMonad m => UnitInfo -> m ()
addUnit u = do
hsc_env <- getSession
logger <- getLogger
newdbs <- case hsc_unit_dbs hsc_env of
Nothing -> panic "addUnit: called too early"
Just dbs ->
let newdb = UnitDatabase
{ unitDatabasePath = "(in memory " ++ showSDoc (hsc_dflags hsc_env) (ppr (unitId u)) ++ ")"
, unitDatabaseUnits = [u]
}
in return (dbs ++ [newdb])
(dbs,unit_state,home_unit) <- liftIO $ initUnits logger (hsc_dflags hsc_env) (Just newdbs)
let unit_env = UnitEnv
{ ue_platform = targetPlatform (hsc_dflags hsc_env)
, ue_namever = ghcNameVersion (hsc_dflags hsc_env)
, ue_home_unit = home_unit
, ue_units = unit_state
}
setSession $ hsc_env
{ hsc_unit_dbs = Just dbs
, hsc_unit_env = unit_env
}
compileInclude :: Int -> (Int, Unit) -> BkpM ()
compileInclude n (i, uid) = do
hsc_env <- getSession
let pkgs = hsc_units hsc_env
msgInclude (i, n) uid
case uid of
HoleUnit -> return ()
RealUnit _ -> return ()
VirtUnit i -> case lookupUnit pkgs uid of
Nothing -> innerBkpM $ compileUnit (instUnitInstanceOf i) (instUnitInsts i)
Just _ -> return ()
type BkpM = IOEnv BkpEnv
data BkpEnv
= BkpEnv {
bkp_session :: Session,
bkp_filename :: FilePath,
bkp_table :: Map IndefUnitId (LHsUnit HsComponentId),
bkp_level :: Int
}
instance HasDynFlags BkpM where
getDynFlags = fmap hsc_dflags getSession
instance HasLogger BkpM where
getLogger = fmap hsc_logger getSession
instance GhcMonad BkpM where
getSession = do
Session s <- fmap bkp_session getEnv
readMutVar s
setSession hsc_env = do
Session s <- fmap bkp_session getEnv
writeMutVar s hsc_env
getBkpEnv :: BkpM BkpEnv
getBkpEnv = getEnv
getBkpLevel :: BkpM Int
getBkpLevel = bkp_level `fmap` getBkpEnv
innerBkpM :: BkpM a -> BkpM a
innerBkpM do_this =
updEnv (\env -> env { bkp_level = bkp_level env + 1 }) do_this
updateEpsGhc_ :: GhcMonad m => (ExternalPackageState -> ExternalPackageState) -> m ()
updateEpsGhc_ f = do
hsc_env <- getSession
liftIO $ atomicModifyIORef' (hsc_EPS hsc_env) (\x -> (f x, ()))
getEpsGhc :: GhcMonad m => m ExternalPackageState
getEpsGhc = do
hsc_env <- getSession
liftIO $ readIORef (hsc_EPS hsc_env)
initBkpM :: FilePath -> [LHsUnit HsComponentId] -> BkpM a -> Ghc a
initBkpM file bkp m =
reifyGhc $ \session -> do
let env = BkpEnv {
bkp_session = session,
bkp_table = Map.fromList [(hsComponentId (unLoc (hsunitName (unLoc u))), u) | u <- bkp],
bkp_filename = file,
bkp_level = 0
}
runIOEnv env m
backpackProgressMsg :: Int -> Logger -> DynFlags -> SDoc -> IO ()
backpackProgressMsg level logger dflags msg =
compilationProgressMsg logger dflags $ text (replicate (level * 2) ' ')
<> msg
mkBackpackMsg :: BkpM Messager
mkBackpackMsg = do
level <- getBkpLevel
return $ \hsc_env mod_index recomp node ->
let dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
state = hsc_units hsc_env
showMsg msg reason =
backpackProgressMsg level logger dflags $ pprWithUnitState state $
showModuleIndex mod_index <>
msg <> showModMsg dflags (recompileRequired recomp) node
<> reason
in case node of
InstantiationNode _ ->
case recomp of
MustCompile -> showMsg (text "Instantiating ") empty
UpToDate
| verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
| otherwise -> return ()
RecompBecause reason -> showMsg (text "Instantiating ") (text " [" <> text reason <> text "]")
ModuleNode _ ->
case recomp of
MustCompile -> showMsg (text "Compiling ") empty
UpToDate
| verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
| otherwise -> return ()
RecompBecause reason -> showMsg (text "Compiling ") (text " [" <> text reason <> text "]")
backpackStyle :: PprStyle
backpackStyle =
mkUserStyle
(QueryQualify neverQualifyNames
alwaysQualifyModules
neverQualifyPackages) AllTheWay
msgTopPackage :: (Int,Int) -> HsComponentId -> BkpM ()
msgTopPackage (i,n) (HsComponentId (PackageName fs_pn) _) = do
dflags <- getDynFlags
logger <- getLogger
level <- getBkpLevel
liftIO . backpackProgressMsg level logger dflags
$ showModuleIndex (i, n) <> text "Processing " <> ftext fs_pn
msgUnitId :: Unit -> BkpM ()
msgUnitId pk = do
dflags <- getDynFlags
logger <- getLogger
hsc_env <- getSession
level <- getBkpLevel
let state = hsc_units hsc_env
liftIO . backpackProgressMsg level logger dflags
$ pprWithUnitState state
$ text "Instantiating "
<> withPprStyle backpackStyle (ppr pk)
msgInclude :: (Int,Int) -> Unit -> BkpM ()
msgInclude (i,n) uid = do
dflags <- getDynFlags
logger <- getLogger
hsc_env <- getSession
level <- getBkpLevel
let state = hsc_units hsc_env
liftIO . backpackProgressMsg level logger dflags
$ pprWithUnitState state
$ showModuleIndex (i, n) <> text "Including "
<> withPprStyle backpackStyle (ppr uid)
type PackageNameMap a = UniqFM PackageName a
unitDefines :: LHsUnit PackageName -> (PackageName, HsComponentId)
unitDefines (L _ HsUnit{ hsunitName = L _ pn@(PackageName fs) })
= (pn, HsComponentId pn (Indefinite (UnitId fs)))
bkpPackageNameMap :: [LHsUnit PackageName] -> PackageNameMap HsComponentId
bkpPackageNameMap units = listToUFM (map unitDefines units)
renameHsUnits :: UnitState -> PackageNameMap HsComponentId -> [LHsUnit PackageName] -> [LHsUnit HsComponentId]
renameHsUnits pkgstate m units = map (fmap renameHsUnit) units
where
renamePackageName :: PackageName -> HsComponentId
renamePackageName pn =
case lookupUFM m pn of
Nothing ->
case lookupPackageName pkgstate pn of
Nothing -> error "no package name"
Just cid -> HsComponentId pn cid
Just hscid -> hscid
renameHsUnit :: HsUnit PackageName -> HsUnit HsComponentId
renameHsUnit u =
HsUnit {
hsunitName = fmap renamePackageName (hsunitName u),
hsunitBody = map (fmap renameHsUnitDecl) (hsunitBody u)
}
renameHsUnitDecl :: HsUnitDecl PackageName -> HsUnitDecl HsComponentId
renameHsUnitDecl (DeclD a b c) = DeclD a b c
renameHsUnitDecl (IncludeD idecl) =
IncludeD IncludeDecl {
idUnitId = fmap renameHsUnitId (idUnitId idecl),
idModRenaming = idModRenaming idecl,
idSignatureInclude = idSignatureInclude idecl
}
renameHsUnitId :: HsUnitId PackageName -> HsUnitId HsComponentId
renameHsUnitId (HsUnitId ln subst)
= HsUnitId (fmap renamePackageName ln) (map (fmap renameHsModuleSubst) subst)
renameHsModuleSubst :: HsModuleSubst PackageName -> HsModuleSubst HsComponentId
renameHsModuleSubst (lk, lm)
= (lk, fmap renameHsModuleId lm)
renameHsModuleId :: HsModuleId PackageName -> HsModuleId HsComponentId
renameHsModuleId (HsModuleVar lm) = HsModuleVar lm
renameHsModuleId (HsModuleId luid lm) = HsModuleId (fmap renameHsUnitId luid) lm
convertHsComponentId :: HsUnitId HsComponentId -> Unit
convertHsComponentId (HsUnitId (L _ hscid) subst)
= mkVirtUnit (hsComponentId hscid) (map (convertHsModuleSubst . unLoc) subst)
convertHsModuleSubst :: HsModuleSubst HsComponentId -> (ModuleName, Module)
convertHsModuleSubst (L _ modname, L _ m) = (modname, convertHsModuleId m)
convertHsModuleId :: HsModuleId HsComponentId -> Module
convertHsModuleId (HsModuleVar (L _ modname)) = mkHoleModule modname
convertHsModuleId (HsModuleId (L _ hsuid) (L _ modname)) = mkModule (convertHsComponentId hsuid) modname
hsunitModuleGraph :: HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph unit = do
hsc_env <- getSession
let decls = hsunitBody unit
pn = hsPackageName (unLoc (hsunitName unit))
home_unit = hsc_home_unit hsc_env
let get_decl (L _ (DeclD hsc_src lmodname mb_hsmod)) =
Just `fmap` summariseDecl pn hsc_src lmodname mb_hsmod
get_decl _ = return Nothing
nodes <- catMaybes `fmap` mapM get_decl decls
let hsig_set = Set.fromList
[ ms_mod_name ms
| ExtendedModSummary { emsModSummary = ms } <- nodes
, ms_hsc_src ms == HsigFile
]
req_nodes <- fmap catMaybes . forM (homeUnitInstantiations home_unit) $ \(mod_name, _) ->
if Set.member mod_name hsig_set
then return Nothing
else fmap (Just . extendModSummaryNoDeps) $ summariseRequirement pn mod_name
return $ mkModuleGraph' $
(ModuleNode <$> (nodes ++ req_nodes)) ++ instantiationNodes (hsc_units hsc_env)
summariseRequirement :: PackageName -> ModuleName -> BkpM ModSummary
summariseRequirement pn mod_name = do
hsc_env <- getSession
let dflags = hsc_dflags hsc_env
let PackageName pn_fs = pn
location <- liftIO $ mkHomeModLocation2 dflags mod_name
(unpackFS pn_fs </> moduleNameSlashes mod_name) "hsig"
env <- getBkpEnv
time <- liftIO $ getModificationUTCTime (bkp_filename env)
hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
mod <- liftIO $ addHomeModuleToFinder hsc_env mod_name location
extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
return ModSummary {
ms_mod = mod,
ms_hsc_src = HsigFile,
ms_location = location,
ms_hs_date = time,
ms_obj_date = Nothing,
ms_iface_date = hi_timestamp,
ms_hie_date = hie_timestamp,
ms_srcimps = [],
ms_textual_imps = extra_sig_imports,
ms_parsed_mod = Just (HsParsedModule {
hpm_module = L loc (HsModule {
hsmodAnn = noAnn,
hsmodLayout = NoLayoutInfo,
hsmodName = Just (L loc mod_name),
hsmodExports = Nothing,
hsmodImports = [],
hsmodDecls = [],
hsmodDeprecMessage = Nothing,
hsmodHaddockModHeader = Nothing
}),
hpm_src_files = []
}),
ms_hspp_file = "",
ms_hspp_opts = dflags,
ms_hspp_buf = Nothing
}
summariseDecl :: PackageName
-> HscSource
-> Located ModuleName
-> Maybe (Located HsModule)
-> BkpM ExtendedModSummary
summariseDecl pn hsc_src (L _ modname) (Just hsmod) = hsModuleToModSummary pn hsc_src modname hsmod
summariseDecl _pn hsc_src lmodname@(L loc modname) Nothing
= do hsc_env <- getSession
r <- liftIO $ summariseModule hsc_env
emptyModNodeMap
(hscSourceToIsBoot hsc_src)
lmodname
True
Nothing
[]
case r of
Nothing -> throwOneError (mkPlainMsgEnvelope loc (text "module" <+> ppr modname <+> text "was not found"))
Just (Left err) -> throwErrors err
Just (Right summary) -> return summary
hsModuleToModSummary :: PackageName
-> HscSource
-> ModuleName
-> Located HsModule
-> BkpM ExtendedModSummary
hsModuleToModSummary pn hsc_src modname
hsmod = do
let imps = hsmodImports (unLoc hsmod)
loc = getLoc hsmod
hsc_env <- getSession
let PackageName unit_fs = pn
dflags = hsc_dflags hsc_env
location0 <- liftIO $ mkHomeModLocation2 dflags modname
(unpackFS unit_fs </>
moduleNameSlashes modname)
(case hsc_src of
HsigFile -> "hsig"
HsBootFile -> "hs-boot"
HsSrcFile -> "hs")
let location = case hsc_src of
HsBootFile -> addBootSuffixLocnOut location0
_ -> location0
env <- getBkpEnv
time <- liftIO $ getModificationUTCTime (bkp_filename env)
hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
let (src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps
ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc . ideclName . unLoc)
ord_idecls
implicit_prelude = xopt LangExt.ImplicitPrelude dflags
implicit_imports = mkPrelImports modname loc
implicit_prelude imps
convImport (L _ i) = (fmap sl_fs (ideclPkgQual i), ideclName i)
extra_sig_imports <- liftIO $ findExtraSigImports hsc_env hsc_src modname
let normal_imports = map convImport (implicit_imports ++ ordinary_imps)
(implicit_sigs, inst_deps) <- liftIO $ implicitRequirementsShallow hsc_env normal_imports
this_mod <- liftIO $ addHomeModuleToFinder hsc_env modname location
return $ ExtendedModSummary
{ emsModSummary =
ModSummary {
ms_mod = this_mod,
ms_hsc_src = hsc_src,
ms_location = location,
ms_hspp_file = (case hiDir dflags of
Nothing -> ""
Just d -> d) </> ".." </> moduleNameSlashes modname <.> "hi",
ms_hspp_opts = dflags,
ms_hspp_buf = Nothing,
ms_srcimps = map convImport src_idecls,
ms_textual_imps = normal_imports
++ extra_sig_imports
++ ((,) Nothing . noLoc <$> implicit_sigs),
ms_parsed_mod = Just (HsParsedModule {
hpm_module = hsmod,
hpm_src_files = []
}),
ms_hs_date = time,
ms_obj_date = Nothing,
ms_iface_date = hi_timestamp,
ms_hie_date = hie_timestamp
}
, emsInstantiatedUnits = inst_deps
}
newUnitId :: IndefUnitId -> Maybe FastString -> UnitId
newUnitId uid mhash = case mhash of
Nothing -> indefUnit uid
Just hash -> UnitId (unitIdFS (indefUnit uid) `appendFS` mkFastString "+" `appendFS` hash)