Skip to content

Commit ce4ea04

Browse files
committed
Improve quick-fix support for "term-level use of type constructors"
1 parent 37fdcf3 commit ce4ea04

File tree

6 files changed

+81
-31
lines changed

6 files changed

+81
-31
lines changed

src/GHC/Diagnostic.hs

Lines changed: 38 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ module GHC.Diagnostic (
1818
, extractIdentifiers
1919
, qualifiedName
2020
, analyzeAnnotation
21+
, takeGhcSourceSpan
2122
, applyReplace
2223
#endif
2324
) where
@@ -65,6 +66,7 @@ formatSolutions start = zipWith formatNumbered [start..] >>> reverse >>> \ case
6566
ImportName module_ qualification name -> importStatement module_ qualification [name] <> faint package
6667
where
6768
package = " (" <> Builder.fromText module_.package <> ")"
69+
AddToImportList module_ text _span -> "Add " <> Builder.fromText text <> " to import list of " <> Builder.fromText module_
6870

6971
faint :: Builder -> Builder
7072
faint = Builder.withSGR [SetConsoleIntensity FaintIntensity]
@@ -98,10 +100,10 @@ annotate getAvailableImports diagnostic = getAvailableImports >>= \ case
98100
++ maybe [] (analyzeAnnotation availableImports) annotation
99101

100102
analyzeHints :: [Text] -> [Solution]
101-
analyzeHints = concat . mapMaybe analyzeHint
103+
analyzeHints = concatMap analyzeHint
102104

103-
analyzeHint :: Text -> Maybe [Solution]
104-
analyzeHint hint = asum [
105+
analyzeHint :: Text -> [Solution]
106+
analyzeHint hint = (fromMaybe [] $ asum [
105107
prefix "Perhaps you intended to use " <&> takeExtensions
106108

107109
, requiredFor GHC_910 $ prefix "Enable any of the following extensions: " <&>
@@ -110,7 +112,7 @@ analyzeHint hint = asum [
110112
, prefix "Perhaps use `" <&> return . takeIdentifier
111113
, prefix "Perhaps use variable `" <&> return . takeIdentifier
112114
, prefix "Perhaps use one of these:" <&> extractIdentifiers
113-
]
115+
]) <> maybeToList addToImportList
114116
where
115117
prefix :: Text -> Maybe Text
116118
prefix p = stripPrefix p hint
@@ -133,6 +135,37 @@ analyzeHint hint = asum [
133135
takeIdentifier :: Text -> Solution
134136
takeIdentifier = UseName . T.takeWhile (/= '\'')
135137

138+
addToImportList :: Maybe Solution
139+
addToImportList = case T.splitOn "' to the import list in the import of `" $ T.unwords $ T.lines $ hint of
140+
[T.takeWhileEnd (/= '`') -> name, T.splitOn "'" -> [module_, r]] -> AddToImportList module_ name <$> do
141+
takeGhcSourceSpan r
142+
_ -> Nothing
143+
144+
takeGhcSourceSpan :: Text -> Maybe Span
145+
takeGhcSourceSpan input = stripPrefix " (at " input <&> T.splitOn ":" >>= \ case
146+
file
147+
: (int -> Just line)
148+
: (T.splitOn "-" . (T.takeWhile (/= ')')) -> [int -> Just start, int -> Just end])
149+
: _ ->
150+
Just $ span file (line, start) (line, end)
151+
152+
file
153+
: (T.splitOn "-" -> [foo -> Just start, (takeFoo >>> foo) -> Just end])
154+
: _ ->
155+
Just $ span file start end
156+
_ -> Nothing
157+
where
158+
span :: Text -> (Int, Int) -> (Int, Int) -> Span
159+
span file start end = Span (T.unpack file) (uncurry Location start) (uncurry Location end)
160+
161+
int :: Text -> Maybe Int
162+
int = T.unpack >>> readMaybe
163+
164+
foo :: Text -> Maybe (Int, Int)
165+
foo = T.unpack >>> readMaybe
166+
167+
takeFoo t = T.take ((T.length $ T.takeWhile (/= ')') t) + 1) t
168+
136169
extractIdentifiers :: Text -> [Solution]
137170
extractIdentifiers input = case T.breakOn "`" >>> snd >>> T.breakOn "\'" $ input of
138171
(T.drop 1 -> identifier, rest)
@@ -307,6 +340,7 @@ edits annotated = case annotated.diagnostic.span of
307340
RemoveImport -> removeLines
308341
UseName name -> Replace span name
309342
ImportName module_ qualification name -> AddImport file module_ qualification [name]
343+
AddToImportList _ text loc -> Replace (Span loc.file loc.end loc.end) $ text <> "(..))" -- FIXME this is not correct and would need HIE lookup
310344

311345
file :: FilePath
312346
file = span.file

src/GHC/Diagnostic/Annotated.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ data Solution =
1515
| RemoveImport
1616
| UseName Text
1717
| ImportName Module Qualification Text
18+
| AddToImportList Text Text Span
1819
deriving (Eq, Show)
1920

2021
data Annotation =

test/GHC/DiagnosticSpec.hs

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -284,13 +284,14 @@ spec = do
284284

285285
test "term-level-use-of-type-constructor" [] [r|
286286
module Foo where
287-
data Foo = Fooa | Fooi
288-
foo = Foo
289-
|] (Just $ TermLevelUseOfTypeConstructor Unqualified "Foo") [
290-
UseName "foo"
291-
, UseName "Fooa"
292-
, UseName "Fooi"
293-
]
287+
import Text.Markdown.Unlit (CodeBlock)
288+
data Foo = CodeBloc
289+
foo = CodeBlock
290+
|] (Just $ TermLevelUseOfTypeConstructor Unqualified "CodeBlock") [
291+
UseName "CodeBloc"
292+
, AddToImportList "Text.Markdown.Unlit" "CodeBlock" (Span "test/fixtures/term-level-use-of-type-constructor/Foo.hs" (Location 2 1) (Location 2 38))
293+
, importName (Module "markdown-unlit" "Text.Markdown.Unlit") "CodeBlock(..)"
294+
]
294295

295296
test "found-hole" [] [r|
296297
module Foo where
@@ -435,7 +436,7 @@ spec = do
435436
requiredFor GHC_910 "Perhaps you intended to use BlockArguments"
436437
, requiredFor GHC_912 "Perhaps you intended to use the `BlockArguments' extension"
437438
]
438-
for_ inputs \ input -> analyzeHint input `shouldBe` Just [
439+
for_ inputs \ input -> analyzeHint input `shouldBe` [
439440
EnableExtension "BlockArguments"
440441
]
441442

@@ -446,7 +447,7 @@ spec = do
446447
requiredFor GHC_910 "Enable any of the following extensions: TemplateHaskell, TemplateHaskellQuotes"
447448
, requiredFor GHC_912 "Perhaps you intended to use the `TemplateHaskellQuotes' extension (implied by `TemplateHaskell')"
448449
]
449-
for_ inputs \ input -> analyzeHint input `shouldBe` Just [
450+
for_ inputs \ input -> analyzeHint input `shouldBe` [
450451
EnableExtension "TemplateHaskellQuotes"
451452
, EnableExtension "TemplateHaskell"
452453
]
@@ -549,6 +550,15 @@ spec = do
549550
analyzeAnnotation availableImports annotation `shouldBe` [
550551
]
551552

553+
fdescribe "takeGhcSourceSpan" do
554+
it "extracts single-line source spans" do
555+
takeGhcSourceSpan " (at Foo.hs:2:1-38).:.:." `shouldBe`
556+
Just (Span "Foo.hs" (Location 2 1) (Location 2 38))
557+
558+
it "extracts multi-line source spans" do
559+
takeGhcSourceSpan " (at Foo.hs:(2,1)-(5,12)).:.:." `shouldBe`
560+
Just (Span "Foo.hs" (Location 2 1) (Location 5 12))
561+
552562
describe "applyReplace" do
553563
it "replaces a given source span with a substitute" do
554564
applyReplace (Location 2 7) (Location 2 14) "filter" [

test/fixtures/term-level-use-of-type-constructor/Foo.hs

Lines changed: 3 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
1-
test/fixtures/term-level-use-of-type-constructor/Foo.hs:3:7: error: [GHC-01928]
2-
• Illegal term-level use of the type constructor `Foo'
3-
• defined at test/fixtures/term-level-use-of-type-constructor/Foo.hs:2:1
4-
• Perhaps use one of these:
5-
variable `foo' (line 3), `Fooa' (line 2), `Fooi' (line 2)
6-
• In the expression: Foo
7-
In an equation for `foo': foo = Foo
1+
test/fixtures/term-level-use-of-type-constructor/Foo.hs:4:7: error: [GHC-01928]
2+
• Illegal term-level use of the type constructor `CodeBlock'
3+
• imported from `Text.Markdown.Unlit' at test/fixtures/term-level-use-of-type-constructor/Foo.hs:2:29-37
4+
• Perhaps use `CodeBloc' (line 3)
5+
Add `CodeBlock' to the import list in the import of
6+
`Text.Markdown.Unlit'
7+
(at test/fixtures/term-level-use-of-type-constructor/Foo.hs:2:1-38).
8+
• In the expression: CodeBlock
9+
In an equation for `foo': foo = CodeBlock
810

test/fixtures/term-level-use-of-type-constructor/err.yaml

Lines changed: 11 additions & 9 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)