summaryrefslogtreecommitdiff
path: root/compiler/GHC/Unit/Module/ModSummary.hs
blob: c584385aef0113b64053725a64c8efd87ec5561c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}

-- | A ModSummary is a node in the compilation manager's dependency graph
-- (ModuleGraph)
module GHC.Unit.Module.ModSummary
   ( ExtendedModSummary (..)
   , extendModSummaryNoDeps
   , ModSummary (..)
   , ms_unitid
   , ms_installed_mod
   , ms_mod_name
   , ms_imps
   , ms_plugin_imps
   , ms_mnwib
   , ms_home_srcimps
   , ms_home_imps
   , msHiFilePath
   , msHsFilePath
   , msObjFilePath
   , msDynObjFilePath
   , 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.Data.Maybe
import GHC.Data.FastString
import GHC.Data.StringBuffer ( StringBuffer )

import GHC.Utils.Fingerprint
import GHC.Utils.Outputable

import Data.Time

-- | Enrichment of 'ModSummary' with backpack dependencies
data ExtendedModSummary = ExtendedModSummary
  { emsModSummary :: {-# UNPACK #-} !ModSummary
  , emsInstantiatedUnits :: [InstantiatedUnit]
  -- ^ Extra backpack deps
  -- NB: This is sometimes left empty in situations where the instantiated units
  -- would not be used. See call sites of 'extendModSummaryNoDeps'.
  }

instance Outputable ExtendedModSummary where
  ppr = \case
    ExtendedModSummary ms bds -> ppr ms <+> ppr bds

extendModSummaryNoDeps :: ModSummary -> ExtendedModSummary
extendModSummaryNoDeps ms = ExtendedModSummary ms []

-- | 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 {
        ms_mod          :: Module,
          -- ^ Identity of the module
        ms_hsc_src      :: HscSource,
          -- ^ The module source either plain Haskell, hs-boot, or hsig
        ms_location     :: ModLocation,
          -- ^ Location of the various files belonging to the module
        ms_hs_hash      :: Fingerprint,
          -- ^ Content hash of source file
        ms_obj_date     :: Maybe UTCTime,
          -- ^ Timestamp of object, if we have one
        ms_dyn_obj_date     :: !(Maybe UTCTime),
          -- ^ Timestamp of dynamic object, if we have one
        ms_iface_date   :: Maybe UTCTime,
          -- ^ Timestamp of hi file, if we have one
          -- See Note [When source is considered modified] and #9243
        ms_hie_date   :: Maybe UTCTime,
          -- ^ Timestamp of hie file, if we have one
        ms_srcimps      :: [(Maybe FastString, Located ModuleName)],
          -- ^ Source imports of the module
        ms_textual_imps :: [(Maybe FastString, Located ModuleName)],
          -- ^ Non-source imports of the module from the module *text*
        ms_ghc_prim_import :: Bool,
          -- ^ Whether the special module GHC.Prim was imported explicitliy
        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.
        ms_hspp_file    :: FilePath,
          -- ^ Filename of preprocessed source file
        ms_hspp_opts    :: DynFlags,
          -- ^ Cached flags from @OPTIONS@, @INCLUDE@ and @LANGUAGE@
          -- pragmas in the modules source code
        ms_hspp_buf     :: Maybe StringBuffer
          -- ^ The actual preprocessed source, if we have it
     }

ms_unitid :: ModSummary -> UnitId
ms_unitid = toUnitId . moduleUnit . ms_mod

ms_installed_mod :: ModSummary -> InstalledModule
ms_installed_mod = fst . getModuleInstantiation . ms_mod

ms_mod_name :: ModSummary -> ModuleName
ms_mod_name = moduleName . ms_mod

-- | Textual imports, plus plugin imports but not SOURCE imports.
ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_imps ms = ms_textual_imps ms ++ ms_plugin_imps ms

-- | Plugin imports
ms_plugin_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
ms_plugin_imps ms = map ((Nothing,) . noLoc) (pluginModNames (ms_hspp_opts ms))

home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
home_imps imps = [ lmodname |  (mb_pkg, lmodname) <- imps,
                                  isLocal mb_pkg ]
  where isLocal Nothing = True
        isLocal (Just pkg) | pkg == fsLit "this" = True -- "this" is special
        isLocal _ = False

-- | Like 'ms_home_imps', but for SOURCE imports.
ms_home_srcimps :: ModSummary -> [Located ModuleName]
ms_home_srcimps = home_imps . 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 -> [Located ModuleName]
ms_home_imps = home_imps . 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, msHiFilePath, msObjFilePath :: ModSummary -> FilePath
msHsFilePath  ms = expectJust "msHsFilePath" (ml_hs_file  (ms_location ms))
msHiFilePath  ms = ml_hi_file  (ms_location ms)
msObjFilePath ms = ml_obj_file (ms_location ms)

msDynObjFilePath :: ModSummary -> DynFlags -> FilePath
msDynObjFilePath ms dflags = dynamicOutputFile dflags (msObjFilePath ms)

-- | Did this 'ModSummary' originate from a hs-boot file?
isBootSummary :: ModSummary -> IsBootInterface
isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot

ms_mnwib :: ModSummary -> ModuleNameWithIsBoot
ms_mnwib ms = GWIB (ms_mod_name ms) (isBootSummary ms)

instance Outputable ModSummary where
   ppr ms
      = sep [text "ModSummary {",
             nest 3 (sep [text "ms_hs_hash = " <> text (show (ms_hs_hash ms)),
                          text "ms_mod =" <+> ppr (ms_mod ms)
                                <> text (hscSourceString (ms_hsc_src ms)) <> comma,
                          text "ms_textual_imps =" <+> ppr (ms_textual_imps ms),
                          text "ms_srcimps =" <+> ppr (ms_srcimps ms)]),
             char '}'
            ]

-- | Find the first target in the provided list which matches the specified
-- 'ModSummary'.
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget ms ts =
  case filter (matches ms) ts of
        []    -> Nothing
        (t:_) -> Just t
  where
    summary `matches` Target { targetId = TargetModule m, targetUnitId = unitId }
        = ms_mod_name summary == m && ms_unitid summary == unitId
    summary `matches` Target { targetId = TargetFile f _, targetUnitId = unitid }
        | Just f' <- ml_hs_file (ms_location summary)
        = f == f'  && ms_unitid summary == unitid
    _ `matches` _
        = False