Skip to content

Commit bd5b9d0

Browse files
authored
Qualified error messages (#938)
* Add a test for #726 * Add a test for #652 * Fix missing qualifiers in code actions
1 parent e24a744 commit bd5b9d0

File tree

2 files changed

+23
-4
lines changed

2 files changed

+23
-4
lines changed

src/Development/IDE/GHC/Error.hs

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,10 +56,16 @@ diagFromText diagSource sev loc msg = (toNormalizedFilePath' $ fromMaybe noFileP
5656
-- | Produce a GHC-style error from a source span and a message.
5757
diagFromErrMsg :: T.Text -> DynFlags -> ErrMsg -> [FileDiagnostic]
5858
diagFromErrMsg diagSource dflags e =
59-
[ diagFromText diagSource sev (errMsgSpan e) $ T.pack $ Out.showSDoc dflags $
60-
ErrUtils.formatErrDoc dflags $ ErrUtils.errMsgDoc e
59+
[ diagFromText diagSource sev (errMsgSpan e)
60+
$ T.pack $ formatErrorWithQual dflags e
6161
| Just sev <- [toDSeverity $ errMsgSeverity e]]
6262

63+
formatErrorWithQual :: DynFlags -> ErrMsg -> String
64+
formatErrorWithQual dflags e =
65+
Out.showSDoc dflags
66+
$ Out.withPprStyle (Out.mkErrStyle dflags $ errMsgContext e)
67+
$ ErrUtils.formatErrDoc dflags
68+
$ ErrUtils.errMsgDoc e
6369

6470
diagFromErrMsgs :: T.Text -> DynFlags -> Bag ErrMsg -> [FileDiagnostic]
6571
diagFromErrMsgs diagSource dflags = concatMap (diagFromErrMsg diagSource dflags) . bagToList

test/exe/Main.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,6 @@ main = do
9797
, rootUriTests
9898
, asyncTests
9999
, clientSettingsTest
100-
101100
, codeActionHelperFunctionTests
102101
]
103102

@@ -1679,6 +1678,19 @@ fillTypedHoleTests = let
16791678
, check "replace _ with foo _"
16801679
"_" "n" "n"
16811680
"(foo _)" "n" "n"
1681+
, testSession "replace _toException with E.toException" $ do
1682+
let mkDoc x = T.unlines
1683+
[ "module Testing where"
1684+
, "import qualified Control.Exception as E"
1685+
, "ioToSome :: E.IOException -> E.SomeException"
1686+
, "ioToSome = " <> x ]
1687+
doc <- createDoc "Test.hs" "haskell" $ mkDoc "_toException"
1688+
_ <- waitForDiagnostics
1689+
actions <- getCodeActions doc (Range (Position 3 0) (Position 3 maxBound))
1690+
chosen <- liftIO $ pickActionWithTitle "replace _toException with E.toException" actions
1691+
executeCodeAction chosen
1692+
modifiedCode <- documentContents doc
1693+
liftIO $ mkDoc "E.toException" @=? modifiedCode
16821694
]
16831695

16841696
addInstanceConstraintTests :: TestTree
@@ -2215,7 +2227,7 @@ addSigLensesTests :: TestTree
22152227
addSigLensesTests = let
22162228
missing = "{-# OPTIONS_GHC -Wmissing-signatures -Wmissing-pattern-synonym-signatures -Wunused-matches #-}"
22172229
notMissing = "{-# OPTIONS_GHC -Wunused-matches #-}"
2218-
moduleH = "{-# LANGUAGE PatternSynonyms #-}\nmodule Sigs where"
2230+
moduleH = "{-# LANGUAGE PatternSynonyms #-}\nmodule Sigs where\nimport qualified Data.Complex as C"
22192231
other = T.unlines ["f :: Integer -> Integer", "f x = 3"]
22202232
before withMissing def
22212233
= T.unlines $ (if withMissing then (missing :) else (notMissing :)) [moduleH, def, other]
@@ -2240,6 +2252,7 @@ addSigLensesTests = let
22402252
, sigSession enableWarnings "a >>>> b = a + b" "(>>>>) :: Num a => a -> a -> a"
22412253
, sigSession enableWarnings "a `haha` b = a b" "haha :: (t1 -> t2) -> t1 -> t2"
22422254
, sigSession enableWarnings "pattern Some a = Just a" "pattern Some :: a -> Maybe a"
2255+
, sigSession enableWarnings "qualifiedSigTest= C.realPart" "qualifiedSigTest :: C.Complex a -> a"
22432256
]
22442257
| (title, enableWarnings) <-
22452258
[("with warnings enabled", True)

0 commit comments

Comments
 (0)