{-# LANGUAGE TupleSections #-}

-- | A ModSummary is a node in the compilation manager's dependency graph
-- (ModuleGraph)
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 for a module node in a 'ModuleGraph'. Module nodes of the module graph
-- are one of:
--
-- * A regular Haskell source module
-- * A hi-boot source module
--
data ModSummary
   = ModSummary {
        ModSummary -> Module
ms_mod          :: Module,
          -- ^ Identity of the module
        ModSummary -> HscSource
ms_hsc_src      :: HscSource,
          -- ^ The module source either plain Haskell, hs-boot, or hsig
        ModSummary -> ModLocation
ms_location     :: ModLocation,
          -- ^ Location of the various files belonging to the module
        ModSummary -> Fingerprint
ms_hs_hash      :: Fingerprint,
          -- ^ Content hash of source file
        ModSummary -> Maybe UTCTime
ms_obj_date     :: Maybe UTCTime,
          -- ^ Timestamp of object, if we have one
        ModSummary -> Maybe UTCTime
ms_dyn_obj_date     :: !(Maybe UTCTime),
          -- ^ Timestamp of dynamic object, if we have one
        ModSummary -> Maybe UTCTime
ms_iface_date   :: Maybe UTCTime,
          -- ^ Timestamp of hi file, if we have one
          -- See Note [When source is considered modified] and #9243
        ModSummary -> Maybe UTCTime
ms_hie_date   :: Maybe UTCTime,
          -- ^ Timestamp of hie file, if we have one
        ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps      :: [(PkgQual, Located ModuleName)], -- FIXME: source imports are never from an external package, why do we allow PkgQual?
          -- ^ Source imports of the module
        ModSummary -> [(PkgQual, Located ModuleName)]
ms_textual_imps :: [(PkgQual, Located ModuleName)],
          -- ^ Non-source imports of the module from the module *text*
        ModSummary -> Bool
ms_ghc_prim_import :: !Bool,
          -- ^ Whether the special module GHC.Prim was imported explicitly
        ModSummary -> Maybe HsParsedModule
ms_parsed_mod   :: Maybe HsParsedModule,
          -- ^ The parsed, nonrenamed source, if we have it.  This is also
          -- used to support "inline module syntax" in Backpack files.
        ModSummary -> FilePath
ms_hspp_file    :: FilePath,
          -- ^ Filename of preprocessed source file
        ModSummary -> DynFlags
ms_hspp_opts    :: DynFlags,
          -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
          -- pragmas in the modules source code
        ModSummary -> Maybe StringBuffer
ms_hspp_buf     :: Maybe StringBuffer
          -- ^ The actual preprocessed source, if we have it
     }

ms_unitid :: ModSummary -> UnitId
ms_unitid :: ModSummary -> UnitId
ms_unitid = Unit -> UnitId
toUnitId (Unit -> UnitId) -> (ModSummary -> Unit) -> ModSummary -> UnitId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit (Module -> Unit) -> (ModSummary -> Module) -> ModSummary -> Unit
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 = (InstalledModule, Maybe InstantiatedModule) -> InstalledModule
forall a b. (a, b) -> a
fst ((InstalledModule, Maybe InstantiatedModule) -> InstalledModule)
-> (ModSummary -> (InstalledModule, Maybe InstantiatedModule))
-> ModSummary
-> InstalledModule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> (InstalledModule, Maybe InstantiatedModule)
getModuleInstantiation (Module -> (InstalledModule, Maybe InstantiatedModule))
-> (ModSummary -> Module)
-> ModSummary
-> (InstalledModule, Maybe InstantiatedModule)
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 = Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (Module -> ModuleName)
-> (ModSummary -> Module) -> ModSummary -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
ms_mod

-- | Textual imports, plus plugin imports but not SOURCE imports.
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 [(PkgQual, Located ModuleName)]
-> [(PkgQual, Located ModuleName)]
-> [(PkgQual, Located ModuleName)]
forall a. [a] -> [a] -> [a]
++ ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps ModSummary
ms

-- | Plugin imports
ms_plugin_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps :: ModSummary -> [(PkgQual, Located ModuleName)]
ms_plugin_imps ModSummary
ms = (ModuleName -> (PkgQual, Located ModuleName))
-> [ModuleName] -> [(PkgQual, Located ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map ((PkgQual
NoPkgQual,) (Located ModuleName -> (PkgQual, Located ModuleName))
-> (ModuleName -> Located ModuleName)
-> ModuleName
-> (PkgQual, Located ModuleName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> Located ModuleName
forall e. e -> Located e
noLoc) (DynFlags -> [ModuleName]
pluginModNames (ModSummary -> DynFlags
ms_hspp_opts ModSummary
ms))

-- | All of the (possibly) home module imports from the given list that is to
-- say, each of these module names could be a home import if an appropriately
-- named file existed.  (This is in contrast to package qualified imports, which
-- are guaranteed not to be home imports.)
home_imps :: [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps :: [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps [(PkgQual, Located ModuleName)]
imps = ((PkgQual, Located ModuleName) -> Bool)
-> [(PkgQual, Located ModuleName)]
-> [(PkgQual, Located ModuleName)]
forall a. (a -> Bool) -> [a] -> [a]
filter (PkgQual -> Bool
maybe_home (PkgQual -> Bool)
-> ((PkgQual, Located ModuleName) -> PkgQual)
-> (PkgQual, Located ModuleName)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PkgQual, Located ModuleName) -> PkgQual
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

-- | Like 'ms_home_imps', but for SOURCE imports.
ms_home_srcimps :: ModSummary -> ([Located ModuleName])
-- [] here because source imports can only refer to the current package.
ms_home_srcimps :: ModSummary -> [Located ModuleName]
ms_home_srcimps = ((PkgQual, Located ModuleName) -> Located ModuleName)
-> [(PkgQual, Located ModuleName)] -> [Located ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (PkgQual, Located ModuleName) -> Located ModuleName
forall a b. (a, b) -> b
snd ([(PkgQual, Located ModuleName)] -> [Located ModuleName])
-> (ModSummary -> [(PkgQual, Located ModuleName)])
-> ModSummary
-> [Located ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(PkgQual, Located ModuleName)] -> [(PkgQual, Located ModuleName)]
home_imps ([(PkgQual, Located ModuleName)]
 -> [(PkgQual, Located ModuleName)])
-> (ModSummary -> [(PkgQual, Located ModuleName)])
-> ModSummary
-> [(PkgQual, Located ModuleName)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps

-- | All of the (possibly) home module imports from a
-- 'ModSummary'; that is to say, each of these module names
-- could be a home import if an appropriately named file
-- existed.  (This is in contrast to package qualified
-- imports, which are guaranteed not to be home imports.)
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 ([(PkgQual, Located ModuleName)]
 -> [(PkgQual, Located ModuleName)])
-> (ModSummary -> [(PkgQual, Located ModuleName)])
-> ModSummary
-> [(PkgQual, Located ModuleName)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> [(PkgQual, Located ModuleName)]
ms_imps

-- The ModLocation contains both the original source filename and the
-- filename of the cleaned-up source file after all preprocessing has been
-- done.  The point is that the summariser will have to cpp/unlit/whatever
-- all files anyway, and there's no point in doing this twice -- just
-- park the result in a temp file, put the name of it in the location,
-- and let @compile@ read from that file on the way back up.

-- The ModLocation is stable over successive up-sweeps in GHCi, wheres
-- the ms_hs_hash and imports can, of course, change

msHsFilePath, msDynHiFilePath, msHiFilePath, msObjFilePath, msDynObjFilePath :: ModSummary -> FilePath
msHsFilePath :: ModSummary -> FilePath
msHsFilePath  ModSummary
ms = FilePath -> Maybe FilePath -> FilePath
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)

-- | Did this 'ModSummary' originate from a hs-boot file?
isBootSummary :: ModSummary -> IsBootInterface
isBootSummary :: ModSummary -> IsBootInterface
isBootSummary ModSummary
ms = if ModSummary -> HscSource
ms_hsc_src ModSummary
ms HscSource -> HscSource -> Bool
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 = ModuleName -> IsBootInterface -> ModuleNameWithIsBoot
forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB (ModSummary -> ModuleName
ms_mod_name ModSummary
ms) (ModSummary -> IsBootInterface
isBootSummary ModSummary
ms)

-- | Returns the dependencies of the ModSummary s.
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 }
                  ]
           ]
        [(PkgQual, GenWithIsBoot (Located ModuleName))]
-> [(PkgQual, GenWithIsBoot (Located ModuleName))]
-> [(PkgQual, GenWithIsBoot (Located ModuleName))]
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
      = [SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ModSummary {",
             Int -> SDoc -> SDoc
nest Int
3 ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_hs_hash = " SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text (Fingerprint -> FilePath
forall a. Show a => a -> FilePath
show (ModSummary -> Fingerprint
ms_hs_hash ModSummary
ms)),
                          FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_mod =" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> Module
ms_mod ModSummary
ms)
                                SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text (HscSource -> FilePath
hscSourceString (ModSummary -> HscSource
ms_hsc_src ModSummary
ms)) SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
forall doc. IsLine doc => doc
comma,
                          FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"unit =" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> UnitId
ms_unitid ModSummary
ms),
                          FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_textual_imps =" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [(PkgQual, Located ModuleName)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(PkgQual, Located ModuleName)]
ms_textual_imps ModSummary
ms),
                          FilePath -> SDoc
forall doc. IsLine doc => FilePath -> doc
text FilePath
"ms_srcimps =" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> [(PkgQual, Located ModuleName)] -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> [(PkgQual, Located ModuleName)]
ms_srcimps ModSummary
ms)]),
             Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'}'
            ]

-- | Find the first target in the provided list which matches the specified
-- 'ModSummary'.
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget ModSummary
ms [Target]
ts =
  case (Target -> Bool) -> [Target] -> [Target]
forall a. (a -> Bool) -> [a] -> [a]
filter (ModSummary -> Target -> Bool
matches ModSummary
ms) [Target]
ts of
        []    -> Maybe Target
forall a. Maybe a
Nothing
        (Target
t:[Target]
_) -> Target -> Maybe 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 ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
m Bool -> Bool -> Bool
&& ModSummary -> UnitId
ms_unitid ModSummary
summary UnitId -> UnitId -> Bool
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 FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
f'  Bool -> Bool -> Bool
&& ModSummary -> UnitId
ms_unitid ModSummary
summary UnitId -> UnitId -> Bool
forall a. Eq a => a -> a -> Bool
== UnitId
unitid
    ModSummary
_ `matches` Target
_
        = Bool
False