Skip to content

Commit 4c335b2

Browse files
committed
Add GHC Structured Error compatibility module
Add compatibility module for GHC's structured error messages. Introduce 'Prism's and 'Lens's to easily access nested structures. Expand documentation for 'StructuredMessage'
1 parent cbbf59f commit 4c335b2

File tree

3 files changed

+91
-4
lines changed

3 files changed

+91
-4
lines changed

ghcide/ghcide.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -153,6 +153,7 @@ library
153153
Development.IDE.GHC.Compat.CmdLine
154154
Development.IDE.GHC.Compat.Driver
155155
Development.IDE.GHC.Compat.Env
156+
Development.IDE.GHC.Compat.Error
156157
Development.IDE.GHC.Compat.Iface
157158
Development.IDE.GHC.Compat.Logger
158159
Development.IDE.GHC.Compat.Outputable
Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
module Development.IDE.GHC.Compat.Error (
3+
-- * Top-level error types and lens for easy access
4+
MsgEnvelope(..),
5+
msgEnvelopeErrorL,
6+
GhcMessage(..),
7+
-- * Error messages for the typechecking and renamer phase
8+
TcRnMessage (..),
9+
TcRnMessageDetailed (..),
10+
flatTcRnMessage,
11+
-- * Parsing error message
12+
PsMessage(..),
13+
-- * Desugaring diagnostic
14+
DsMessage (..),
15+
-- * Driver error message
16+
DriverMessage (..),
17+
-- * General Diagnostics
18+
Diagnostic(..),
19+
-- * Prisms for error selection
20+
_TcRnMessage,
21+
_GhcPsMessage,
22+
_GhcDsMessage,
23+
_GhcDriverMessage,
24+
) where
25+
26+
import Control.Lens
27+
import GHC.Driver.Errors.Types
28+
import GHC.HsToCore.Errors.Types
29+
import GHC.Tc.Errors.Types
30+
import GHC.Types.Error
31+
32+
_TcRnMessage :: Prism' GhcMessage TcRnMessage
33+
_TcRnMessage = prism' GhcTcRnMessage (\case
34+
GhcTcRnMessage tcRnMsg -> Just tcRnMsg
35+
_ -> Nothing)
36+
37+
_GhcPsMessage :: Prism' GhcMessage PsMessage
38+
_GhcPsMessage = prism' GhcPsMessage (\case
39+
GhcPsMessage psMsg -> Just psMsg
40+
_ -> Nothing)
41+
42+
_GhcDsMessage :: Prism' GhcMessage DsMessage
43+
_GhcDsMessage = prism' GhcDsMessage (\case
44+
GhcDsMessage dsMsg -> Just dsMsg
45+
_ -> Nothing)
46+
47+
_GhcDriverMessage :: Prism' GhcMessage DriverMessage
48+
_GhcDriverMessage = prism' GhcDriverMessage (\case
49+
GhcDriverMessage driverMsg -> Just driverMsg
50+
_ -> Nothing)
51+
52+
-- | Some 'TcRnMessage's are nested in other constructors for additional context.
53+
-- For example, 'TcRnWithHsDocContext' and 'TcRnMessageWithInfo'.
54+
-- However, in some occasions you don't need the additional context and you just want
55+
-- the error message. @'flatTcRnMessage'@ recursively unwraps these constructors,
56+
-- until there are no more constructors with additional context.
57+
--
58+
flatTcRnMessage :: TcRnMessage -> TcRnMessage
59+
flatTcRnMessage = \case
60+
TcRnWithHsDocContext _ tcMsg -> flatTcRnMessage tcMsg
61+
TcRnMessageWithInfo _ (TcRnMessageDetailed _ tcMsg) -> flatTcRnMessage tcMsg
62+
msg -> msg
63+
64+
msgEnvelopeErrorL :: Lens' (MsgEnvelope e) e
65+
msgEnvelopeErrorL = lens errMsgDiagnostic (\envelope e -> envelope { errMsgDiagnostic = e } )

ghcide/src/Development/IDE/Types/Diagnostics.hs

Lines changed: 25 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,8 @@ module Development.IDE.Types.Diagnostics (
1414
fdShouldShowDiagnosticL,
1515
fdStructuredMessageL,
1616
StructuredMessage(..),
17+
_NoStructuredMessage,
18+
_SomeStructuredMessage,
1719
IdeResult,
1820
LSP.DiagnosticSeverity(..),
1921
DiagnosticStore,
@@ -192,6 +194,23 @@ instance NFData ShowDiagnostic where
192194
-- force the GhcMessage inside, so that we can derive Show, Eq, Ord, NFData on
193195
-- FileDiagnostic. FileDiagnostic only uses this as metadata so we can safely
194196
-- ignore it in fields.
197+
--
198+
-- Instead of pattern matching on these constructors directly, consider 'Prism' from
199+
-- the 'lens' package. This allows to conveniently pattern match deeply into the 'MsgEnvelope GhcMessage'
200+
-- constructor.
201+
-- The module 'Development.IDE.GHC.Compat.Error' implements additional 'Lens's and 'Prism's,
202+
-- allowing you to avoid importing GHC modules directly.
203+
--
204+
-- For example, to pattern match on a 'TcRnMessage' you can use the lens:
205+
--
206+
-- @
207+
-- message ^? _SomeStructuredMessage . msgEnvelopeErrorL . _TcRnMessage
208+
-- @
209+
--
210+
-- This produces a value of type `Maybe TcRnMessage`.
211+
--
212+
-- Further, consider utility functions such as 'flatTcRnMessage', which strip
213+
-- context from error messages which may be more convenient in certain situations.
195214
data StructuredMessage
196215
= NoStructuredMessage
197216
| SomeStructuredMessage (MsgEnvelope GhcMessage)
@@ -244,10 +263,6 @@ data FileDiagnostic = FileDiagnostic
244263

245264
instance NFData FileDiagnostic
246265

247-
makeLensesWith
248-
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))
249-
''FileDiagnostic
250-
251266
prettyRange :: Range -> Doc Terminal.AnsiStyle
252267
prettyRange Range{..} = f _start <> "-" <> f _end
253268
where f Position{..} = pretty (show $ _line+1) <> colon <> pretty (show $ _character+1)
@@ -314,3 +329,9 @@ srenderColored =
314329

315330
defaultTermWidth :: Int
316331
defaultTermWidth = 80
332+
333+
makePrisms ''StructuredMessage
334+
335+
makeLensesWith
336+
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))
337+
''FileDiagnostic

0 commit comments

Comments
 (0)