{-# LANGUAGE TupleSections #-}
module GHC.Unit.Module.ModSummary
( ModSummary (..)
, ms_unitid
, ms_installed_mod
, ms_mod_name
, ms_imps
, ms_plugin_imps
, ms_mnwib
, ms_home_srcimps
, ms_home_imps
, msHiFilePath
, msDynHiFilePath
, msHsFilePath
, msObjFilePath
, msDynObjFilePath
, msDeps
, isBootSummary
, findTarget
)
where
import GHC.Prelude
import GHC.Hs
import GHC.Driver.Session
import GHC.Unit.Types
import GHC.Unit.Module
import GHC.Types.SourceFile ( HscSource(..), hscSourceString )
import GHC.Types.SrcLoc
import GHC.Types.Target
import GHC.Types.PkgQual
import GHC.Data.Maybe
import GHC.Data.StringBuffer ( StringBuffer )
import GHC.Utils.Fingerprint
import GHC.Utils.Outputable
import Data.Time
data ModSummary
= ModSummary {
ModSummary -> Module
ms_mod :: Module,
ModSummary -> HscSource
ms_hsc_src :: HscSource,
ModSummary -> ModLocation
ms_location :: ModLocation,
ModSummary -> Fingerprint
ms_hs_hash :: Fingerprint,
ModSummary -> Maybe UTCTime
ms_obj_date :: Maybe UTCTime,
ModSummary -> Maybe UTCTime
ms_dyn_obj_date :: !(Maybe UTCTime),
ModSummary -> Maybe UTCTime
ms_iface_date :: Maybe UTCTime,
ModSummary -> Maybe UTCTime
ms_hie_date :: Maybe UTCTime,
ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps :: [(PkgQual, Located ModuleName)],
ModSummary -> [(PkgQual, Located ModuleName)]
ms_textual_imps :: [(PkgQual, Located ModuleName)],
ModSummary -> Bool
ms_ghc_prim_import :: !Bool,
ModSummary -> Maybe HsParsedModule
ms_parsed_mod :: Maybe HsParsedModule,
ModSummary -> FilePath
ms_hspp_file :: FilePath,
ModSummary -> DynFlags
ms_hspp_opts :: DynFlags,
ModSummary -> Maybe StringBuffer
ms_hspp_buf :: Maybe StringBuffer
}
ms_unitid :: ModSummary -> UnitId
ms_unitid :: ModSummary -> UnitId
ms_unitid = Unit -> UnitId
toUnitId forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall unit. GenModule unit -> unit
moduleUnit forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
ms_installed_mod :: ModSummary -> InstalledModule
ms_installed_mod :: ModSummary -> InstalledModule
ms_installed_mod = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> (InstalledModule, Maybe InstantiatedModule)
getModuleInstantiation forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
ms_mod_name :: ModSummary -> ModuleName
ms_mod_name :: ModSummary -> ModuleName
ms_mod_name = forall unit. GenModule unit -> ModuleName
moduleName forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod
ms_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_imps ModSummary
ms = ModSummary -> [(PkgQual, Located ModuleName)]
ms_textual_imps ModSummary
ms forall a. [a] -> [a] -> [a]
++ ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps ModSummary
ms
ms_plugin_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps ModSummary
ms = forall a b. (a -> b) -> [a] -> [b]
map ((PkgQual
NoPkgQual,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. e -> Located e
noLoc) (DynFlags -> [ModuleName]
pluginModNames (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms))
home_imps :: [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps :: [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps [(PkgQual, Located ModuleName)]
imps = forall a. (a -> Bool) -> [a] -> [a]
filter (PkgQual -> Bool
maybe_home forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(PkgQual, Located ModuleName)]
imps
where maybe_home :: PkgQual -> Bool
maybe_home PkgQual
NoPkgQual = Bool
True
maybe_home (ThisPkg UnitId
_) = Bool
True
maybe_home (OtherPkg UnitId
_) = Bool
False
ms_home_srcimps :: ModSummary -> ([Located ModuleName])
ms_home_srcimps :: ModSummary -> [Located ModuleName]
ms_home_srcimps = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps
ms_home_imps :: ModSummary -> ([(PkgQual, Located ModuleName)])
ms_home_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_home_imps = [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> [(PkgQual, Located ModuleName)]
ms_imps
msHsFilePath, msDynHiFilePath, msHiFilePath, msObjFilePath, msDynObjFilePath :: ModSummary -> FilePath
msHsFilePath :: ModSummary -> FilePath
msHsFilePath ModSummary
ms = forall a. HasCallStack => FilePath -> Maybe a -> a
expectJust FilePath
"msHsFilePath" (ModLocation -> Maybe FilePath
ml_hs_file (ModSummary -> ModLocation
ms_location ModSummary
ms))
msHiFilePath :: ModSummary -> FilePath
msHiFilePath ModSummary
ms = ModLocation -> FilePath
ml_hi_file (ModSummary -> ModLocation
ms_location ModSummary
ms)
msDynHiFilePath :: ModSummary -> FilePath
msDynHiFilePath ModSummary
ms = ModLocation -> FilePath
ml_dyn_hi_file (ModSummary -> ModLocation
ms_location ModSummary
ms)
msObjFilePath :: ModSummary -> FilePath
msObjFilePath ModSummary
ms = ModLocation -> FilePath
ml_obj_file (ModSummary -> ModLocation
ms_location ModSummary
ms)
msDynObjFilePath :: ModSummary -> FilePath
msDynObjFilePath ModSummary
ms = ModLocation -> FilePath
ml_dyn_obj_file (ModSummary -> ModLocation
ms_location ModSummary
ms)
isBootSummary :: ModSummary -> IsBootInterface
isBootSummary :: ModSummary -> IsBootInterface
isBootSummary ModSummary
ms = if ModSummary -> HscSource
ms_hsc_src ModSummary
ms forall a. Eq a => a -> a -> Bool
== HscSource
HsBootFile then IsBootInterface
IsBoot else IsBootInterface
NotBoot
ms_mnwib :: ModSummary -> ModuleNameWithIsBoot
ms_mnwib :: ModSummary -> ModuleNameWithIsBoot
ms_mnwib ModSummary
ms = forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB (ModSummary -> ModuleName
ms_mod_name ModSummary
ms) (ModSummary -> IsBootInterface
isBootSummary ModSummary
ms)
msDeps :: ModSummary -> ([(PkgQual, GenWithIsBoot (Located ModuleName))])
msDeps :: ModSummary -> [(PkgQual, GenWithIsBoot (Located ModuleName))]
msDeps ModSummary
s =
[ (PkgQual
NoPkgQual, GenWithIsBoot (Located ModuleName)
d)
| Located ModuleName
m <- ModSummary -> [Located ModuleName]
ms_home_srcimps ModSummary
s
, GenWithIsBoot (Located ModuleName)
d <- [ GWIB { gwib_mod :: Located ModuleName
gwib_mod = Located ModuleName
m, gwib_isBoot :: IsBootInterface
gwib_isBoot = IsBootInterface
IsBoot }
]
]
forall a. [a] -> [a] -> [a]
++ [ (PkgQual
pkg, (GWIB { gwib_mod :: Located ModuleName
gwib_mod = Located ModuleName
m, gwib_isBoot :: IsBootInterface
gwib_isBoot = IsBootInterface
NotBoot }))
| (PkgQual
pkg, Located ModuleName
m) <- ModSummary -> [(PkgQual, Located ModuleName)]
ms_imps ModSummary
s
]
instance Outputable ModSummary where
ppr :: ModSummary -> SDoc
ppr ModSummary
ms
= forall doc. IsLine doc => [doc] -> doc
sep [forall doc. IsLine doc => FilePath -> doc
text FilePath
"ModSummary {",
Int -> SDoc -> SDoc
nest Int
3 (forall doc. IsLine doc => [doc] -> doc
sep [forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_hs_hash = " forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => FilePath -> doc
text (forall a. Show a => a -> FilePath
show (ModSummary -> Fingerprint
ms_hs_hash ModSummary
ms)),
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_mod =" forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr (ModSummary -> Module
ms_mod ModSummary
ms)
forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => FilePath -> doc
text (HscSource -> FilePath
hscSourceString (ModSummary -> HscSource
ms_hsc_src ModSummary
ms)) forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => doc
comma,
forall doc. IsLine doc => FilePath -> doc
text FilePath
"unit =" forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr (ModSummary -> UnitId
ms_unitid ModSummary
ms),
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_textual_imps =" forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(PkgQual, Located ModuleName)]
ms_textual_imps ModSummary
ms),
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_srcimps =" forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps ModSummary
ms)]),
forall doc. IsLine doc => Char -> doc
char Char
'}'
]
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget ModSummary
ms [Target]
ts =
case forall a. (a -> Bool) -> [a] -> [a]
filter (ModSummary -> Target -> Bool
matches ModSummary
ms) [Target]
ts of
[] -> forall a. Maybe a
Nothing
(Target
t:[Target]
_) -> forall a. a -> Maybe a
Just Target
t
where
ModSummary
summary matches :: ModSummary -> Target -> Bool
`matches` Target { targetId :: Target -> TargetId
targetId = TargetModule ModuleName
m, targetUnitId :: Target -> UnitId
targetUnitId = UnitId
unitId }
= ModSummary -> ModuleName
ms_mod_name ModSummary
summary forall a. Eq a => a -> a -> Bool
== ModuleName
m Bool -> Bool -> Bool
&& ModSummary -> UnitId
ms_unitid ModSummary
summary forall a. Eq a => a -> a -> Bool
== UnitId
unitId
ModSummary
summary `matches` Target { targetId :: Target -> TargetId
targetId = TargetFile FilePath
f Maybe Phase
_, targetUnitId :: Target -> UnitId
targetUnitId = UnitId
unitid }
| Just FilePath
f' <- ModLocation -> Maybe FilePath
ml_hs_file (ModSummary -> ModLocation
ms_location ModSummary
summary)
= FilePath
f forall a. Eq a => a -> a -> Bool
== FilePath
f' Bool -> Bool -> Bool
&& ModSummary -> UnitId
ms_unitid ModSummary
summary forall a. Eq a => a -> a -> Bool
== UnitId
unitid
ModSummary
_ `matches` Target
_
= Bool
False