TL;DR Starting from version 9.4, GHC will have a completely revamped API to deal with diagnostics (i.e. warnings or errors), moving away from loosely-structured strings in favour of richer Haskell types. This will make it easier to develop IDEs and other tools that work with GHC’s diagnostics.

Well-Typed was able to carry out this work thanks to Richard Eisenberg, as part of NSF grant number 1704041.

Introduction

The topic of “Can we please have better IDEs?” crops up now and again within the Haskell community. Over the years tools like Haskell Language Server dramatically improved the situation, but all these tools had to deal with one constant factor: the limitations of the GHC API, in particular how it emitted diagnostics.

Previously, diagnostics were emitted as structured documents (SDocs), which can be seen as strings with a richer API to control their layout when being pretty-printed. Once GHC emitted a diagnostic as an SDoc, the best tools could do was to parse the text hoping to regain some structure out of it. Consider the following error:

AnyM.hs:12:3: error:
    Illegal bang-pattern (use BangPatterns):
    ! res
   |
12 |   !res <- anyM (pure . (==) 5) [1..]
   |   ^^^^

Here most tools have to work unnecessarily hard, in order to:1

  1. Find out the diagnostic’s precise location, by parsing the filename:line:column on the first line.
  2. Understand whether this is an error or a warning (and perhaps the specific warning flag used) by parsing the rest of the first line.
  3. Determine the meaning of the diagnostic (e.g. that this is a parse error due to use of a bang-pattern when the BangPatterns extension is not enabled).
  4. If the diagnostic includes extra context like involved types or variables, further parse and analyse the text to extract such information for later use.
  5. Parse any hints present in the diagnostic (in this case use BangPatterns), turning them into automated refactorings that the user may wish to apply.

This is surely not very ergonomic for GHC API users, and with this in mind, Alp Mestanogullari wrote GHC proposal #306 to improve the situation, and this was subsequently implemented by Alfredo Di Napoli working with Richard Eisenberg.

In this blog post, we will explore what lies in store in future releases of GHC when it comes to diagnostic messages. Part 1 explains the new diagnostic API design at a high level, and Part 2 summarizes further possibilities that this work enables, including a low-barrier way to get started contributing to GHC. If you’d prefer a larger example, the Appendix demonstrates a tiny tool that uses the GHC API to parse a module and give customised errors and hints for some categories of diagnostics.

Part 1: Representing diagnostics in the GHC API

A diagnostic is a fact that GHC emits about the compiled program. These diagnostics always arise for a particular reason, such as a warning flag being enabled or a type error GHC can’t recover from. However, there is a fluid relationship between warnings and errors in GHC: for example, -Werror turns warnings into errors. Thus we refer to “diagnostics” or “messages” to encompass both.

Our work focused on creating a richer hierarchy of diagnostic types that can be returned by the GHC API functions instead of an opaque SDoc. The key idea is to have datatypes describing the meaning of errors, rather than their presentation. As an example, the TcRnMessage type describes diagnostics that may be emitted by the type-checker:

data TcRnMessage where
  TcRnUnknownMessage      :: (Diagnostic a, Typeable a) => a -> TcRnMessage
  TcRnUnusedPatternBinds  :: HsBind GhcRn -> TcRnMessage
  TcRnDodgyImports        :: RdrName -> TcRnMessage
  ...

The GhcMessage type unifies diagnostics that may be generated across different phases of compilation:

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.
  GhcUnknownMessage :: (Diagnostic a, Typeable a) => a -> GhcMessage

Each message is then wrapped into a MsgEnvelope (as we will see later) to store metadata such as the source position. Given a TcRnMessage, tools can simply pattern match to interpret the diagnostic and extract the information they need. However, they will also need to render the message for the user or retrieve any hints, and this is where the new Diagnostic typeclass comes into play.

The Diagnostic typeclass

The Diagnostic typeclass is defined as such:

class Diagnostic a where
  diagnosticMessage :: a -> DecoratedSDoc
  diagnosticReason  :: a -> DiagnosticReason
  diagnosticHints   :: a -> [GhcHint]

This specifies the common interface supported by diagnostic types such as TcRnMessage. It includes:

  • The diagnosticMessage: how this diagnostic can be presented to the user as text (structured for pretty-printing).

  • The diagnosticReason: why this diagnostic arose, for example due to an error or a warning controlled by a specific flag. There is a subtle but important nuance behind this field, discussed below.

  • The diagnosticHints: a list of hints that tools can use to present users with refactoring suggestions. For example, this may include a value like SuggestExtension BangPatterns if enabling the extension may fix the error.

Representing “unknown” diagnostics

The astute reader probably noticed the following data constructor for a TcRnMessage (and similarly for GhcMessage):

...
  TcRnUnknownMessage :: (Diagnostic a, Typeable a) => a -> TcRnMessage
...

This constructor serves two purposes. First of all, it allows us to gradually port the existing GHC SDoc diagnostics to the new API without having to do it all in one go. GHC emits a lot of diagnostics, so only a subset have been ported and new errors and warnings are converted day after day. In the meantime, we can simply wrap all the existing SDoc into a generic DiagnosticMessage (which has a suitable Diagnostic instance) and pass it to the TcRnUnknownMessage.

Second, this constructor makes the diagnostic infrastructure extensible: tools building on the GHC API and performing their own checks, such as the LiquidHaskell GHC plugin, will be able to define their own diagnostic types.

Messages and envelopes

A diagnostic type such as TcRnMessage or GhcMessage captures the meaning of the warning or error, but not the context in which it arose. For that, the GHC API wraps it in a MsgEnvelope:

data MsgEnvelope e = MsgEnvelope
   { errMsgSpan        :: SrcSpan
   , errMsgContext     :: PrintUnqualified
   , errMsgDiagnostic  :: e
   , errMsgSeverity    :: Severity
   } deriving (Functor, Foldable, Traversable)

Hopefully this type is fairly self explanatory:

  • The errMsgSpan carries the range of source positions to which the message relates.
  • The errMsgContext is a minor detail, determining whether names are printed with or without module qualifiers.
  • The errMsgDiagnostic is the payload of the message, for example a TcRnMessage or GhcMessage.
  • The errMsgSeverity is the severity of the message, to which we turn now.

Reason and severity

It isn’t immediately obvious why a MsgEnvelope contains a Severity, while the Diagnostic class includes a function returning a DiagnosticReason, since these might seem overlapping. Let’s take a look at their definitions first:

data Severity
  = SevIgnore
  | SevWarning
  | SevError

data DiagnosticReason
  = WarningWithoutFlag
  | WarningWithFlag !WarningFlag
  | ErrorWithoutFlag
  deriving (Eq, Show)

While it looks like they might be unified, they actually serve two different purposes: the Severity is an enumeration that indicates how GHC will report this message to the user (or not at all, in case of a SevIgnore). The DiagnosticReason instead gives the reason why the diagnostic was generated by GHC in the first place.

This arises from the fluid relationship between errors and warnings in GHC. For example, a diagnostic might be created due to the -Wunused-imports warning flag, but with -Werror enabled, so it should be treated as an error, not a warning. Thus the Severity will be SevError whereas the DiagnosticReason will be WarningWithFlag Opt_WarnUnusedImports. Keeping separate the “nature of the message” vs. “how the message should be treated,” we are able to capture both concepts without information loss.

The DiagnosticReason is determined by the diagnosticReason class method as a fixed function of the diagnostic type, and never changes. In contrast, the Severity is computed dynamically depending on the flags enabled at the point in the GHC session where the message is emitted, and hence must be stored as part of the MsgEnvelope.

Part 2: Applications and further work

Refactoring GHC this way has been a long and sometimes tricky process, but we hope it will bring many benefits to the ecosystem. In this section we will explore next steps and possible projects that could put this work to use.

Completing the refactoring

We have completed the foundations, but there is still lots to be done, as described in #19905. The good news is that the majority of diagnostics still not ported are not too hard to convert, and these kind of tasks are well suited as a first ticket for somebody who is looking for an opportunity to contribute to GHC.

We have written a collection of self-contained and self-explanatory tickets, which are labelled error messages+newcomer+task in the GHC issue tracker. A typical ticket (such as #20119) gives a high level overview of what needs to be done together with a possible plan of action, mentioning a couple of key modules to get people started.

We have already been delighted to see some new GHC contributors getting started through this work!

Haskell Language Server integration

A key motivation for this refactoring work was to enable HLS to consume GHC’s diagnostics more conveniently, rather than needing to parse them with regular expressions. This is being discussed on HLS issue #2014. It will take a bit of time before HLS can start incorporating the new infrastructure and reap its benefits, because HLS will need to be adapted to deal with the substantial changes in the GHC API in versions 9.2 and 9.4.

GHC unique diagnostic codes

There was a recent surge of interest in GHC proposal #325, which suggests diagnostics should be given unique reference IDs a la Rust, for example:

> class a

<interactive>:5:7: error:
    [GHCERR_b356c55] Malformed head of type or class declaration: a

The idea is that the unique ID (here GHCERR_b356c55) is easier to search for, or look up in a reference document, than a longer message that may change between compiler releases.

Doing this using the old SDoc-based infrastructure in GHC would have been daunting and potentially very error prone: using the new diagnostic infrastructure this seems fairly easy now. As a small proof of concept, we could simply add an ADT enumerating all the diagnostics:

data DiagnosticId
  = GHCERR_01
  | GHCERR_02
  | GHCWARN_01
  | ...

Then we could extend the Diagnostic typeclass to require that each diagnostic must return an identifier:

class Diagnostic a where
  diagnosticId      :: a -> DiagnosticId
  diagnosticMessage :: a -> DecoratedSDoc
  diagnosticReason  :: a -> DiagnosticReason
  diagnosticHints   :: a -> [GhcHint]

Last but not least, when displaying messages we could now pretty-print the relevant diagnostic and its ID (together with a URL pointing to the relevant section in the GHC manual, for example). The extra typeclass method will ensure that diagnosticId is automatically accessible as part of the normal GHC API.

Diagnostic message plugins

GHC already has an extensive plugin mechanism that allows developers to modify certain stages of the compilation pipeline, for example to add optimization passes or adjust the type-checker’s behaviour. A “diagnostic message plugin” would allow users to intercept a diagnostic message before it gets printed, so that they can manipulate it, for example to add domain-specific error information. This could just be a hook in the form of an effectful function GhcMessage -> m GhcMessage that would be called by GHC before we pretty-print the message, where the monad m would allow side-effects such as IO, looking up data in the GHC API session and so on.

For example, a plugin to search for unknown function identifiers on Hoogle might look something like this2:

data HoogleSeacher = HoogleSeacher {
    originalMessage  :: TcRnMessage
  , foundIdentifiers :: [JSON.Value]
  }

instance Diagnostic HoogleSeacher
  diagnosticReason = diagnosticReason . originalMessage
  diagnosticMessage (HoogleSeacher msg foundIdentifiers) = diagnosticReason msg `unionDecoratedSDoc` ...
     -- Print the original message, together with any identifiers fetched from Hoogle

hooglePlugin :: DiagnosticPlugin
hooglePlugin = defaultDiagnosticPlugin { onGhcMessage = searchHoogle }
  where
    searchHoogle :: GhcMonad m => GhcMessage -> m GhcMessage
    searchHoogle = \case
      GhcTcRnMessage (msg@TcRnOutOfScope{outOfScopeName})
        -> do let query = "https://hoogle.haskell.org?mode=json&hoogle=" <> outOfScopeName
              results <- -- issue a HTTP query and decode the resulting JSON
              pure $ GhcUnknownMessage (HoogleSeacher msg results)
      x -> pure x

JSON output from GHC

It would be nice to give GHC the ability to emit structured diagnostics in JSON, when a particular flag is set. This would mean that tools not able to use the GHC API directly could simply call GHC with this flag and parse the output JSON into something structured they can manipulate.

GHC already supports a -ddump-json flag, but its semantics is largely unspecified and it does not currently leverage the new representation of diagnostic messages. There has been some discussion in ticket #19278 on what a potential JSON interface could look like. The final design hasn’t been decided yet, so if you have any valuable input or feedback on what you would like to see, that ticket is the one to monitor closely.

Conclusion

I (Alfredo) would like to personally thank Richard Eisenberg for the valuable contributions during this work and for all the “rebuttals” which ultimately led to the final design. The original “diagnostic message plugin” idea was suggested to me by my colleague Andres Löh.

While doing this refactoring work, we kept in mind real world use cases, trying to come up with an API that would maximise reuse in IDEs and other third party tools. Having said that, it’s always hard to guess what would be most useful to others, and this is why we would love to hear from you if you have a tool you think could benefit from the new GHC API. It would be great to receive feedback on whether or not this work is actually making your life easier. Please get in touch via the GHC issue tracker (in particular #19905) or the ghc-devs mailing list.

Well-Typed are always open to working on projects that benefit GHC and the surrounding Haskell ecosystem. Please email info@well-typed.com if you’d like to discuss how we can help with your open-source or commercial project.

Appendix: Example tool to customize errors

Here’s an example of a tiny tool that uses the GHC API to parse a module and give customised errors and hints for some categories of diagnostics. It runs an interactive GHC session via the runGhc function, tries to parse the input module and returns either a collection of diagnostics including some errors, or a successfully parsed module. If there are parse errors, it pretty-prints them using custom functions.

Ignoring the technical details, the key functions are prettyPrintError and reworkBangPatterns, where we were able to work with a typed representation of diagnostics and their hints. This was not possible with previous versions of GHC: in their case, errs would be just a collection of SDocs, and the best thing we could have done would have been to parse the SDocs to recover any extra information.

The full code is available here. It requires a recent build of GHC HEAD or GHC 9.4 (when available).3

playground :: FilePath
           -- ^ The module we would like to compile, with extension (e.g. "AnyM.hs")
           -> IO ()
playground filename = do
  res <- runGhc (Just myGhcLibDir) $ do
    df <- getSessionDynFlags

    setSessionDynFlags $ df { ghcLink        = LinkInMemory
                            , ghcMode        = CompManager
                            , extensionFlags = EnumSet.empty
                            }

    hsc_env <- getSession
    mb_emod <- first (fmap GhcDriverMessage) <$> liftIO (summariseFile hsc_env [] fn Nothing Nothing)
    case mb_emod of
      Left errs  -> pure $ Left errs
      Right emod -> handleSourceError (pure . Left . srcErrorMessages)
                                      (Right <$> parseModule (emsModSummary emod))

  case res of
    Left errs -> do
      putStrLn "Errors:"
      putStrLn $ showPprUnsafe . ppr $ formatBulleted defaultSDocContext $
        (mkDecorated $ map (prettyPrintError . errMsgDiagnostic) (bagToList . getMessages $ errs))
    Right ps  -> do
      -- Do something with the parsed module.
      putStrLn $ showPprUnsafe (pm_parsed_source ps)

  where

    prettyPrintError :: GhcMessage -> SDoc
    prettyPrintError msg =
      let body  = case msg of
            GhcPsMessage (PsErrNumUnderscores _)
              -> vcat [ text "You are trying to use the underscore (_) to separate the digits"
                      , text "but this syntax is not standard Haskell2010 syntax."
                      ]
            _ -> vcat . unDecorated $ diagnosticMessage msg
          hints = map reworkBangPatterns (diagnosticHints msg)
      in vcat [
             body
           , hang (text "Hints:") 2 (vcat hints)
           ]

    reworkBangPatterns :: GhcHint -> SDoc
    reworkBangPatterns h = ppr $ case h of
      SuggestSingleExtension _ LangExt.BangPatterns
        -> text "Uh-oh, you need to enable BangPatterns! :)"
      x -> ppr x

...

For example, here’s a trivial Haskell program containing some parse errors:

module Main where

import Data.Foldable

anyM :: (Monad m, Foldable t) => (a -> m Bool) -> t a -> m Bool
anyM f = foldrM (\v acc -> do { v <- f v; if v then pure True else pure acc}) False

main :: IO ()
main = do
  !res <- anyM (pure . (==) 5) [10_000 ..]
  print res

Running the program above on this program (saved as AnyM.hs) produces something like this:

/Users/adinapoli/programming/haskell/playground/AnyM.hs:10:3: error:
    Illegal bang-pattern
    !res
    Suggested fix: Perhaps you intended to use BangPatterns
   |
10 |   !res <- anyM (pure . (==) 5) [10_000 ..]
   |   ^^^^

/Users/adinapoli/programming/haskell/playground/AnyM.hs:10:33: error:
    Illegal underscores in integer literals
    Suggested fix: Perhaps you intended to use NumericUnderscores
   |
10 |   !res <- anyM (pure . (==) 5) [10_000 ..]
   |                                 ^^^^^^
Errors:
* You are trying to use the underscore (_) to separate the digits
  but this syntax is not standard Haskell2010 syntax.
  Hints: Perhaps you intended to use NumericUnderscores
* Illegal bang-pattern
  !res
  Hints: Uh-oh, you need to enable BangPatterns! :)

The first two messages are part of the standard output that GHC would normally emit, whereas the last part is our little tool in action.


  1. If we were dealing directly with the output of a GHC API call rather than a diagnostic as printed on stdout by GHC we would have avoided steps 1 and 2 but the rest would still have been necessary.↩︎

  2. This is obviously a fictional example, just to demonstrate a semi-interesting usage of the plugin. Furthermore, at the time of writing, the TcRnOutOfScope constructor has not yet been ported.↩︎

  3. The GHC version will need to include commit 06d1ca856d3374bf8dac952740cfe4cef76a350d. Of course it is possible that subsequent GHC API changes will require changes to the code.↩︎