summaryrefslogtreecommitdiff
path: root/compiler/GHC/Driver/Errors/Types.hs
blob: cbf06220259d734a3e6c6c7ca18d54df9addd226 (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
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}

module GHC.Driver.Errors.Types (
    GhcMessage(..)
  , GhcMessageOpts(..)
  , DriverMessage(..)
  , DriverMessageOpts(..)
  , DriverMessages, PsMessage(PsHeaderMessage)
  , WarningMessages
  , ErrorMessages
  , WarnMsg
  -- * Constructors
  , ghcUnknownMessage
  -- * Utility functions
  , hoistTcRnMessage
  , hoistDsMessage
  , checkBuildingCabalPackage
  ) where

import GHC.Prelude

import Data.Bifunctor
import Data.Typeable

import GHC.Driver.Session (DynFlags, PackageArg, gopt)
import GHC.Driver.Flags (GeneralFlag (Opt_BuildingCabalPackage))
import GHC.Types.Error
import GHC.Unit.Module
import GHC.Unit.State

import GHC.Parser.Errors.Types ( PsMessage(PsHeaderMessage) )
import GHC.HsToCore.Errors.Types ( DsMessage )
import GHC.Hs.Extension          (GhcTc)

import Language.Haskell.Syntax.Decls (RuleDecl)

import GHC.Generics ( Generic )

import GHC.Tc.Errors.Types
import GHC.Iface.Errors.Types

-- | A collection of warning messages.
-- /INVARIANT/: Each 'GhcMessage' in the collection should have 'SevWarning' severity.
type WarningMessages = Messages GhcMessage

-- | A collection of error messages.
-- /INVARIANT/: Each 'GhcMessage' in the collection should have 'SevError' severity.
type ErrorMessages   = Messages GhcMessage

-- | A single warning message.
-- /INVARIANT/: It must have 'SevWarning' severity.
type WarnMsg         = MsgEnvelope GhcMessage


{- Note [GhcMessage]
~~~~~~~~~~~~~~~~~~~~

We might need to report diagnostics (error and/or warnings) to the users. The
'GhcMessage' type is the root of the diagnostic hierarchy.

It's useful to have a separate type constructor for the different stages of
the compilation pipeline. This is not just helpful for tools, as it gives a
clear indication on where the error occurred exactly. Furthermore it increases
the modularity amongst the different components of GHC (i.e. to avoid having
"everything depend on everything else") and allows us to write separate
functions that renders the different kind of messages.

-}

-- | The umbrella type that encompasses all the different messages that GHC
-- might output during the different compilation stages. See
-- Note [GhcMessage].
data GhcMessage where
  -- | A message from the parsing phase.
  GhcPsMessage      :: PsMessage -> GhcMessage
  -- | A message from typecheck/renaming phase.
  GhcTcRnMessage    :: TcRnMessage -> GhcMessage
  -- | A message from the desugaring (HsToCore) phase.
  GhcDsMessage      :: DsMessage -> GhcMessage
  -- | A message from the driver.
  GhcDriverMessage  :: DriverMessage -> GhcMessage

  -- | An \"escape\" hatch which can be used when we don't know the source of
  -- the message or if the message is not one of the typed ones. The
  -- 'Diagnostic' and 'Typeable' constraints ensure that if we /know/, at
  -- pattern-matching time, the originating type, we can attempt a cast and
  -- access the fully-structured error. This would be the case for a GHC
  -- plugin that offers a domain-specific error type but that doesn't want to
  -- place the burden on IDEs/application code to \"know\" it. The
  -- 'Diagnostic' constraint ensures that worst case scenario we can still
  -- render this into something which can be eventually converted into a
  -- 'DecoratedSDoc'.
  GhcUnknownMessage :: UnknownDiagnostic -> GhcMessage

  deriving Generic


data GhcMessageOpts = GhcMessageOpts { psMessageOpts :: DiagnosticOpts PsMessage
                                     , tcMessageOpts :: DiagnosticOpts TcRnMessage
                                     , dsMessageOpts :: DiagnosticOpts DsMessage
                                     , driverMessageOpts :: DiagnosticOpts DriverMessage
                                     }

-- | Creates a new 'GhcMessage' out of any diagnostic. This function is also
-- provided to ease the integration of #18516 by allowing diagnostics to be
-- wrapped into the general (but structured) 'GhcMessage' type, so that the
-- conversion can happen gradually. This function should not be needed within
-- GHC, as it would typically be used by plugin or library authors (see
-- comment for the 'GhcUnknownMessage' type constructor)
ghcUnknownMessage :: (DiagnosticOpts a ~ NoDiagnosticOpts, Diagnostic a, Typeable a) => a -> GhcMessage
ghcUnknownMessage = GhcUnknownMessage . UnknownDiagnostic

-- | Abstracts away the frequent pattern where we are calling 'ioMsgMaybe' on
-- the result of 'IO (Messages TcRnMessage, a)'.
hoistTcRnMessage :: Monad m => m (Messages TcRnMessage, a) -> m (Messages GhcMessage, a)
hoistTcRnMessage = fmap (first (fmap GhcTcRnMessage))

-- | Abstracts away the frequent pattern where we are calling 'ioMsgMaybe' on
-- the result of 'IO (Messages DsMessage, a)'.
hoistDsMessage :: Monad m => m (Messages DsMessage, a) -> m (Messages GhcMessage, a)
hoistDsMessage = fmap (first (fmap GhcDsMessage))

-- | A collection of driver messages
type DriverMessages = Messages DriverMessage

-- | A message from the driver.
data DriverMessage where
  -- | Simply wraps a generic 'Diagnostic' message @a@.
  DriverUnknownMessage :: UnknownDiagnostic -> DriverMessage

  -- | A parse error in parsing a Haskell file header during dependency
  -- analysis
  DriverPsHeaderMessage :: !PsMessage -> DriverMessage

  {-| DriverMissingHomeModules is a warning (controlled with -Wmissing-home-modules) that
      arises when running GHC in --make mode when some modules needed for compilation
      are not included on the command line. For example, if A imports B, `ghc --make
      A.hs` will cause this warning, while `ghc --make A.hs B.hs` will not.

      Useful for cabal to ensure GHC won't pick up modules listed neither in
      'exposed-modules' nor in 'other-modules'.

      Test case: warnings/should_compile/MissingMod

  -}
  DriverMissingHomeModules :: UnitId -> [ModuleName] -> !BuildingCabalPackage -> DriverMessage

  {-| DriverUnknown is a warning that arises when a user tries to
      reexport a module which isn't part of that unit.
  -}
  DriverUnknownReexportedModules :: UnitId -> [ModuleName] -> DriverMessage

  {-| DriverUnknownHiddenModules is a warning that arises when a user tries to
      hide a module which isn't part of that unit.
  -}
  DriverUnknownHiddenModules :: UnitId -> [ModuleName] -> DriverMessage

  {-| DriverUnusedPackages occurs when when package is requested on command line,
      but was never needed during compilation. Activated by -Wunused-packages.

     Test cases: warnings/should_compile/UnusedPackages
  -}
  DriverUnusedPackages :: [(UnitId, PackageName, Version, PackageArg)] -> DriverMessage

  {-| DriverUnnecessarySourceImports (controlled with -Wunused-imports) occurs if there
      are {-# SOURCE #-} imports which are not necessary. See 'warnUnnecessarySourceImports'
      in 'GHC.Driver.Make'.

     Test cases: warnings/should_compile/T10637
  -}
  DriverUnnecessarySourceImports :: !ModuleName -> DriverMessage

  {-| DriverDuplicatedModuleDeclaration occurs if a module 'A' is declared in
       multiple files.

     Test cases: None.
  -}
  DriverDuplicatedModuleDeclaration :: !Module -> [FilePath] -> DriverMessage

  {-| DriverModuleNotFound occurs if a module 'A' can't be found.

     Test cases: None.
  -}
  DriverModuleNotFound :: !ModuleName -> DriverMessage

  {-| DriverFileModuleNameMismatch occurs if a module 'A' is defined in a file with a different name.
      The first field is the name written in the source code; the second argument is the name extracted
      from the filename.

     Test cases: module/mod178, /driver/bug1677
  -}
  DriverFileModuleNameMismatch :: !ModuleName -> !ModuleName -> DriverMessage

  {-| DriverUnexpectedSignature occurs when GHC encounters a module 'A' that imports a signature
      file which is neither in the 'signatures' section of a '.cabal' file nor in any package in
      the home modules.

      Example:

      -- MyStr.hsig is defined, but not added to 'signatures' in the '.cabal' file.
      signature MyStr where
          data Str

      -- A.hs, which tries to import the signature.
      module A where
      import MyStr


     Test cases: driver/T12955
  -}
  DriverUnexpectedSignature :: !ModuleName -> !BuildingCabalPackage -> GenInstantiations UnitId -> DriverMessage

  {-| DriverFileNotFound occurs when the input file (e.g. given on the command line) can't be found.

     Test cases: None.
  -}
  DriverFileNotFound :: !FilePath -> DriverMessage

  {-| DriverStaticPointersNotSupported occurs when the 'StaticPointers' extension is used
       in an interactive GHCi context.

     Test cases: ghci/scripts/StaticPtr
  -}
  DriverStaticPointersNotSupported :: DriverMessage

  {-| DriverBackpackModuleNotFound occurs when Backpack can't find a particular module
      during its dependency analysis.

     Test cases: -
  -}
  DriverBackpackModuleNotFound :: !ModuleName -> DriverMessage

  {-| DriverUserDefinedRuleIgnored is a warning that occurs when user-defined rules
      are ignored. This typically happens when Safe Haskell.

     Test cases:

       tests/safeHaskell/safeInfered/UnsafeWarn05
       tests/safeHaskell/safeInfered/UnsafeWarn06
       tests/safeHaskell/safeInfered/UnsafeWarn07
       tests/safeHaskell/safeInfered/UnsafeInfered11
       tests/safeHaskell/safeLanguage/SafeLang03
  -}
  DriverUserDefinedRuleIgnored :: !(RuleDecl GhcTc) -> DriverMessage

  {-| DriverMixedSafetyImport is an error that occurs when a module is imported
      both as safe and unsafe.

    Test cases:

      tests/safeHaskell/safeInfered/Mixed03
      tests/safeHaskell/safeInfered/Mixed02

  -}
  DriverMixedSafetyImport :: !ModuleName -> DriverMessage

  {-| DriverCannotLoadInterfaceFile is an error that occurs when we cannot load the interface
      file for a particular module. This can happen for example in the context of Safe Haskell,
      when we have to load a module to check if it can be safely imported.

    Test cases: None.

  -}
  DriverCannotLoadInterfaceFile :: !Module -> DriverMessage

  {-| DriverInferredSafeImport is a warning (controlled by the Opt_WarnSafe flag)
      that occurs when a module is inferred safe.

    Test cases: None.

  -}
  DriverInferredSafeModule :: !Module -> DriverMessage

  {-| DriverMarkedTrustworthyButInferredSafe is a warning (controlled by the Opt_WarnTrustworthySafe flag)
      that occurs when a module is marked trustworthy in SafeHaskell but it has been inferred safe.

    Test cases:
      tests/safeHaskell/safeInfered/TrustworthySafe02
      tests/safeHaskell/safeInfered/TrustworthySafe03

  -}
  DriverMarkedTrustworthyButInferredSafe :: !Module -> DriverMessage

  {-| DriverInferredSafeImport is a warning (controlled by the Opt_WarnInferredSafeImports flag)
      that occurs when a safe-inferred module is imported from a safe module.

    Test cases: None.

  -}
  DriverInferredSafeImport :: !Module -> DriverMessage

  {-| DriverCannotImportUnsafeModule is an error that occurs when an usafe module
      is being imported from a safe one.

    Test cases: None.

  -}
  DriverCannotImportUnsafeModule :: !Module -> DriverMessage

  {-| DriverMissingSafeHaskellMode is a warning (controlled by the Opt_WarnMissingSafeHaskellMode flag)
      that occurs when a module is using SafeHaskell features but SafeHaskell mode is not enabled.

    Test cases: None.

  -}
  DriverMissingSafeHaskellMode :: !Module -> DriverMessage

  {-| DriverPackageNotTrusted is an error that occurs when a package is required to be trusted
      but it isn't.

    Test cases:
      tests/safeHaskell/check/Check01
      tests/safeHaskell/check/Check08
      tests/safeHaskell/check/Check06
      tests/safeHaskell/check/pkg01/ImpSafeOnly09
      tests/safeHaskell/check/pkg01/ImpSafe03
      tests/safeHaskell/check/pkg01/ImpSafeOnly07
      tests/safeHaskell/check/pkg01/ImpSafeOnly08

  -}
  DriverPackageNotTrusted :: !UnitState -> !UnitId -> DriverMessage

  {-| DriverCannotImportFromUntrustedPackage is an error that occurs in the context of
      Safe Haskell when trying to import a module coming from an untrusted package.

    Test cases:
      tests/safeHaskell/check/Check09
      tests/safeHaskell/check/pkg01/ImpSafe01
      tests/safeHaskell/check/pkg01/ImpSafe04
      tests/safeHaskell/check/pkg01/ImpSafeOnly03
      tests/safeHaskell/check/pkg01/ImpSafeOnly05
      tests/safeHaskell/flags/SafeFlags17
      tests/safeHaskell/flags/SafeFlags22
      tests/safeHaskell/flags/SafeFlags23
      tests/safeHaskell/ghci/p11
      tests/safeHaskell/ghci/p12
      tests/safeHaskell/ghci/p17
      tests/safeHaskell/ghci/p3
      tests/safeHaskell/safeInfered/UnsafeInfered01
      tests/safeHaskell/safeInfered/UnsafeInfered02
      tests/safeHaskell/safeInfered/UnsafeInfered02
      tests/safeHaskell/safeInfered/UnsafeInfered03
      tests/safeHaskell/safeInfered/UnsafeInfered05
      tests/safeHaskell/safeInfered/UnsafeInfered06
      tests/safeHaskell/safeInfered/UnsafeInfered09
      tests/safeHaskell/safeInfered/UnsafeInfered10
      tests/safeHaskell/safeInfered/UnsafeInfered11
      tests/safeHaskell/safeInfered/UnsafeWarn01
      tests/safeHaskell/safeInfered/UnsafeWarn03
      tests/safeHaskell/safeInfered/UnsafeWarn04
      tests/safeHaskell/safeInfered/UnsafeWarn05
      tests/safeHaskell/unsafeLibs/BadImport01
      tests/safeHaskell/unsafeLibs/BadImport06
      tests/safeHaskell/unsafeLibs/BadImport07
      tests/safeHaskell/unsafeLibs/BadImport08
      tests/safeHaskell/unsafeLibs/BadImport09
      tests/safeHaskell/unsafeLibs/Dep05
      tests/safeHaskell/unsafeLibs/Dep06
      tests/safeHaskell/unsafeLibs/Dep07
      tests/safeHaskell/unsafeLibs/Dep08
      tests/safeHaskell/unsafeLibs/Dep09
      tests/safeHaskell/unsafeLibs/Dep10

  -}
  DriverCannotImportFromUntrustedPackage :: !UnitState -> !Module -> DriverMessage

  DriverRedirectedNoMain :: !ModuleName -> DriverMessage

  DriverHomePackagesNotClosed :: ![UnitId] -> DriverMessage

  DriverInterfaceError :: !IfaceMessage -> DriverMessage

deriving instance Generic DriverMessage

data DriverMessageOpts =
  DriverMessageOpts { psDiagnosticOpts :: DiagnosticOpts PsMessage
                    , ifaceDiagnosticOpts :: DiagnosticOpts IfaceMessage }


-- | Checks if we are building a cabal package by consulting the 'DynFlags'.
checkBuildingCabalPackage :: DynFlags -> BuildingCabalPackage
checkBuildingCabalPackage dflags =
  if gopt Opt_BuildingCabalPackage dflags
     then YesBuildingCabalPackage
     else NoBuildingCabalPackage