Skip to content

Difficulties with integration with source plugins #2779

Open
@edsko

Description

@edsko

Consider this minimal source plugin which whenever it encounters the expression False checks if ScopedTypeVariables are enabled, and if not, throws an error:

{-# LANGUAGE CPP #-}

module SayYes (plugin) where

import Control.Monad
import Data.Data
import Data.Generics
import Language.Haskell.TH (Extension(..))

#if __GLASGOW_HASKELL__ < 900
import Bag
import ErrUtils
import GHC
import GhcPlugins
#else
import GHC.Data.Bag
import GHC.Hs
import GHC.Plugins
import GHC.Utils.Error
#endif

plugin :: Plugin
plugin = defaultPlugin { parsedResultAction = \_ _ -> action }

action :: HsParsedModule -> Hsc HsParsedModule
action parsed@HsParsedModule{hpm_module = m} =
    (\m' -> parsed {hpm_module = m'}) <$>
      gmapM (everywhereM (mkM sayYes)) m

sayYes :: HsExpr GhcPs -> Hsc (HsExpr GhcPs)
sayYes e = do
   case e of
     HsVar _ (L l x) | occNameString (rdrNameOcc x) == "False" -> do
       dynFlags <- getDynFlags
       unless (ScopedTypeVariables `xopt` dynFlags) $
         issueError l $ text "Everyone needs scoped type variables"
       return $ e
     _otherwise  ->
       return $ e

issueError :: SrcSpan -> SDoc -> Hsc a
issueError l errMsg = do
    dynFlags <- getDynFlags
    throwOneError $
      mkErrMsg dynFlags l neverQualify errMsg

issueWarning :: SrcSpan -> SDoc -> Hsc ()
issueWarning l errMsg = do
    dynFlags <- getDynFlags
    liftIO $ printOrThrowWarnings dynFlags . listToBag . (:[]) $
      mkWarnMsg dynFlags l neverQualify errMsg

Example use case:

-- {-# LANGUAGE ScopedTypeVariables #-}

{-# OPTIONS_GHC -fplugin=SayYes #-}

module Main where

main :: IO ()
main = print False

If we compile this on the command line (say, with cabal), we get

app/Main.hs:8:14: error: Everyone needs scoped type variables
  |
8 | main = print False
  |              ^^^^^

unless we enable the pragma. All good.

If we open a project with HLS and open Main.hs, there are two orthogonal problems:

  1. The error triggers whether or not the language pragma is actually enabled. Curiously, if we use issueWarning instead of issueError, the opposite is true: we never see the warning at all.
  2. The location of the error that is being reported is wrong (compiler:1:1 instead of the correct location within the source program).

(Tested with ghc 8.8.4, 8.10.7 and 9.0.2. Full example code at https://github.com/well-typed/large-records/tree/edsko/hls-bugreport/hls-plugin-integration .)

Metadata

Metadata

Assignees

No one assigned

    Labels

    component: ghcidetype: bugSomething isn't right: doesn't work as intended, documentation is missing/outdated, etc..

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions