Skip to content
This repository was archived by the owner on Jan 2, 2021. It is now read-only.

Remove language extension completions. #948

Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
43 changes: 3 additions & 40 deletions src/Development/IDE/Plugin/CodeAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,10 +49,8 @@ import Data.Char
import Data.Maybe
import Data.List.Extra
import qualified Data.Text as T
import Data.Tuple.Extra ((&&&))
import Text.Regex.TDFA (mrAfter, (=~), (=~~))
import Outputable (ppr, showSDocUnsafe)
import GHC.LanguageExtensions.Type (Extension)
import Data.Function
import Control.Arrow ((>>>))
import Data.Functor
Expand Down Expand Up @@ -157,8 +155,7 @@ suggestAction
-> [(T.Text, [TextEdit])]
suggestAction packageExports ideOptions parsedModule text diag = concat
-- Order these suggestions by priority
[ suggestAddExtension diag -- Highest priority
, suggestSignature True diag
[ suggestSignature True diag
, suggestExtendImport packageExports text diag
, suggestFillTypeWildcard diag
, suggestFixConstructorImport text diag
Expand Down Expand Up @@ -518,40 +515,6 @@ suggestFillTypeWildcard Diagnostic{_range=_range,..}
= [("Use type signature: ‘" <> typeSignature <> "’", [TextEdit _range typeSignature])]
| otherwise = []

suggestAddExtension :: Diagnostic -> [(T.Text, [TextEdit])]
suggestAddExtension Diagnostic{_range=_range,..}
-- File.hs:22:8: error:
-- Illegal lambda-case (use -XLambdaCase)
-- File.hs:22:6: error:
-- Illegal view pattern: x -> foo
-- Use ViewPatterns to enable view patterns
-- File.hs:26:8: error:
-- Illegal `..' in record pattern
-- Use RecordWildCards to permit this
-- File.hs:53:28: error:
-- Illegal tuple section: use TupleSections
-- File.hs:238:29: error:
-- * Can't make a derived instance of `Data FSATrace':
-- You need DeriveDataTypeable to derive an instance for this class
-- * In the data declaration for `FSATrace'
-- C:\Neil\shake\src\Development\Shake\Command.hs:515:31: error:
-- * Illegal equational constraint a ~ ()
-- (Use GADTs or TypeFamilies to permit this)
-- * In the context: a ~ ()
-- While checking an instance declaration
-- In the instance declaration for `Unit (m a)'
| exts@(_:_) <- filter (`Map.member` ghcExtensions) $ T.split (not . isAlpha) $ T.replace "-X" "" _message
= [("Add " <> x <> " extension", [TextEdit (Range (Position 0 0) (Position 0 0)) $ "{-# LANGUAGE " <> x <> " #-}\n"]) | x <- exts]
| otherwise = []

-- | All the GHC extensions
ghcExtensions :: Map.HashMap T.Text Extension
ghcExtensions = Map.fromList . filter notStrictFlag . map ( ( T.pack . flagSpecName ) &&& flagSpecFlag ) $ xFlags
where
-- Strict often causes false positives, as in Data.Map.Strict imports.
-- See discussion at https://github.com/haskell/ghcide/pull/638
notStrictFlag (name, _) = name /= "Strict"

suggestModuleTypo :: Diagnostic -> [(T.Text, [TextEdit])]
suggestModuleTypo Diagnostic{_range=_range,..}
-- src/Development/IDE/Core/Compile.hs:58:1: error:
Expand Down Expand Up @@ -648,7 +611,7 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
| Just (binding, mod_srcspan) <-
matchRegExMultipleImports _message
, Just c <- contents
= mod_srcspan >>= (\(x, y) -> suggestions c binding x y)
= mod_srcspan >>= (\(x, y) -> suggestions c binding x y)
| otherwise = []
where
suggestions c binding mod srcspan
Expand All @@ -664,7 +627,7 @@ suggestExtendImport exportsMap contents Diagnostic{_range=_range,..}
renderImport IdentInfo {parent, rendered}
| Just p <- parent = p <> "(" <> rendered <> ")"
| otherwise = rendered
lookupExportMap binding mod
lookupExportMap binding mod
| Just match <- Map.lookup binding (getExportsMap exportsMap)
, [(ident, _)] <- filter (\(_,m) -> mod == m) (Set.toList match)
= Just ident
Expand Down
13 changes: 3 additions & 10 deletions src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,6 @@ import Type
import Packages
#if MIN_GHC_API_VERSION(8,10,0)
import Predicate (isDictTy)
import GHC.Platform
import Pair
import Coercion
#endif
Expand Down Expand Up @@ -560,8 +559,10 @@ getCompletions ideOpts CC { allModNamesAsNS, unqualCompls, qualCompls, importabl
result
| "import " `T.isPrefixOf` fullLine
= filtImportCompls
-- we leave this condition here to avoid duplications and return empty list
-- since HLS implements this completion (#haskell-language-server/pull/662)
| "{-# language" `T.isPrefixOf` T.toLower fullLine
= filtOptsCompls languagesAndExts
= []
| "{-# options_ghc" `T.isPrefixOf` T.toLower fullLine
= filtOptsCompls (map (T.pack . stripLeading '-') $ flagsForCompletion False)
| "{-# " `T.isPrefixOf` fullLine
Expand All @@ -574,14 +575,6 @@ getCompletions ideOpts CC { allModNamesAsNS, unqualCompls, qualCompls, importabl
return result


-- The supported languages and extensions
languagesAndExts :: [T.Text]
#if MIN_GHC_API_VERSION(8,10,0)
languagesAndExts = map T.pack $ GHC.supportedLanguagesAndExtensions ( PlatformMini ArchUnknown OSUnknown )
#else
languagesAndExts = map T.pack GHC.supportedLanguagesAndExtensions
#endif

-- ---------------------------------------------------------------------
-- helper functions for pragmas
-- ---------------------------------------------------------------------
Expand Down
69 changes: 10 additions & 59 deletions test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -547,7 +547,6 @@ codeActionTests = testGroup "code actions"
, removeImportTests
, extendImportTests
, suggestImportTests
, addExtensionTests
, fixConstructorImportTests
, importRenameActionTests
, fillTypedHoleTests
Expand Down Expand Up @@ -1038,7 +1037,7 @@ extendImportTests = testGroup "extend import actions"
, "import ModuleA (A(Constructor))"
, "b :: A"
, "b = Constructor"
])
])
, testSession "extend single line import with mixed constructors" $ template
[("ModuleA.hs", T.unlines
[ "module ModuleA where"
Expand Down Expand Up @@ -1230,63 +1229,6 @@ suggestImportTests = testGroup "suggest import actions"
else
liftIO $ [_title | CACodeAction CodeAction{_title} <- actions, _title == newImp ] @?= []


addExtensionTests :: TestTree
addExtensionTests = testGroup "add language extension actions"
[ testSession "add NamedFieldPuns language extension" $ template
(T.unlines
[ "module Module where"
, ""
, "data A = A { getA :: Bool }"
, ""
, "f :: A -> Bool"
, "f A { getA } = getA"
])
(Range (Position 0 0) (Position 0 0))
"Add NamedFieldPuns extension"
(T.unlines
[ "{-# LANGUAGE NamedFieldPuns #-}"
, "module Module where"
, ""
, "data A = A { getA :: Bool }"
, ""
, "f :: A -> Bool"
, "f A { getA } = getA"
])
, testSession "add RecordWildCards language extension" $ template
(T.unlines
[ "module Module where"
, ""
, "data A = A { getA :: Bool }"
, ""
, "f :: A -> Bool"
, "f A { .. } = getA"
])
(Range (Position 0 0) (Position 0 0))
"Add RecordWildCards extension"
(T.unlines
[ "{-# LANGUAGE RecordWildCards #-}"
, "module Module where"
, ""
, "data A = A { getA :: Bool }"
, ""
, "f :: A -> Bool"
, "f A { .. } = getA"
])
]
where
template initialContent range expectedAction expectedContents = do
doc <- createDoc "Module.hs" "haskell" initialContent
_ <- waitForDiagnostics
CACodeAction action@CodeAction { _title = actionTitle } : _
<- sortOn (\(CACodeAction CodeAction{_title=x}) -> x) <$>
getCodeActions doc range
liftIO $ expectedAction @=? actionTitle
executeCodeAction action
contentAfterAction <- documentContents doc
liftIO $ expectedContents @=? contentAfterAction


insertNewDefinitionTests :: TestTree
insertNewDefinitionTests = testGroup "insert new definition actions"
[ testSession "insert new function definition" $ do
Expand Down Expand Up @@ -2952,7 +2894,16 @@ nonLocalCompletionTests =
Just (List [TextEdit {_range = Range {_start = Position {_line = 1, _character = 44}, _end = Position {_line = 1, _character = 44}}, _newText = "FormatParse, "}])),
("FormatParse", CiSnippet, "FormatParse {fpModifiers=${1:_fpModifiers}, fpChar=${2:_fpChar}, fpRest=${3:_fpRest}}", False, False,
Just (List [TextEdit {_range = Range {_start = Position {_line = 1, _character = 44}, _end = Position {_line = 1, _character = 44}}, _newText = "FormatParse, "}]))
],
-- we need this test to make sure the ghcide completions module does not return completions for language pragmas. this functionality is turned on in hls
completionTest
"do not show pragma completions"
[ "{-# LANGUAGE ",
"{module A where}",
"main = return ()"
]
(Position 0 13)
[]
]

otherCompletionTests :: [TestTree]
Expand Down