Saturday, February 23, 2019

Adding a GHC Language Extension

Adding a GHC Language Extension

This note summarizes the essential mechanics of adding a new language extension to GHC. The example code will illustrate adding a Foo extension.

Implementing the extension

The first step is to add a Foo constructor to the Extension type in libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs.

data Extension
    = Cpp
    | OverlappingInstances
    ...
    | Foo

The next job is to extend xFlagsDeps in compiler/main/DynFlags.hs.

xFlagsDeps = [
  flagSpec "AllowAmbiguousTypes" LangExt.AllowAmbiguousTypes,
  ...
  flagSpec "Foo"                 LangExt.Foo
]

That's all it takes. With these two changes, it is now possible to enable Foo in Haskell source files by writing {-# LANGUAGE Foo #-} or from a compile command by passing the argument -XFoo.

Testing for the extension

Lexer

In compiler/parser/Lexer.x, locate data ExtBits and add a constructor for Foo.

data ExtBits
  = FfiBit
  | ...
  | FooBit
Next, extend the where clause of function mkParserFlags' with a case for Foo.
langExtBits =
        FfiBit `xoptBit` LangExt.ForeignFunctionInterface
    .|. InterruptibleFfiBit `xoptBit` LangExt.InterruptibleFFI

    ...

    .|. FooBit `xoptBit` LangExt.FooBit
  
The function xtest is then the basic building block for testing if Foo is enabled. For example, this specific function tests a bitmap for the on/off status of the Foo bit.
fooEnabled :: ExtsBitMap -> Bool
fooEnabled = xtest FooBit
In practice, testing for a language extension in the lexer is called from a function computing a lexer action. Suppose foo to be such a function and the action it computes depends somehow on whether the Foo language extension is in effect. Putting it all together, schematically it will have the following form.
foo :: (FastString -> Token) -> Action
foo con span buf len = do
    exts <- getExts
    if FooBit `xtest` exts then
       ...
    else
       ...

Parser

This utility computes a monadic expression testing for the on/off state of a bit in a parser state monad.

extension :: (ExtsBitmap -> Bool) -> P Bool
extension p = P $ \s -> POk s (p $! (pExtsBitmap . options) s)
An expression of this kind can be evaluated in the semantic action of a parse rule in compiler/parser/Parser.y. Here's an example of how one might be used.
foo :: { () }
  : 'foo'  {}
  | {- empty -}    {% do
                         foo_required <- extension fooEnabled
                         when foo_required $ do
                           loc <- fileSrcSpan
                           parseErrorSDoc loc $ text "Missing foo"
                    }

Renaming, type-checking and de-sugaring

All of renaming, typechecking and desurgaring occur in the contexts of TcRnIf _ _ monads. Function xoptM :: Extension -> TcRnIf gbl lcl Bool is provided for extension testing in such contexts. Here's a schematic of how such a test might be used in a renaming function.

import GHC.LanguageExtensions

updateFoos :: [AvailInfo] -> RnM (TcGlbEnv, TcLclEnv)
updateFoos info = do
  (globals, locals) <- getEnvs
  opt_Foo <- xoptM Foo
  if not opt_Foo then
    return (globals, locals)
  else
    let globals' = ...
        locals' = ...
    return (globals', locals')