Skip to content

Commit

Permalink
Suggest open imports (haskell/ghcide#740)
Browse files Browse the repository at this point in the history
Also fixes two bugs with qualified imports

Fixes haskell/ghcide#480
  • Loading branch information
pepeiborra committed Sep 2, 2020
1 parent f67dd5a commit 050d988
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 5 deletions.
15 changes: 10 additions & 5 deletions ghcide/src/Development/IDE/Plugin/CodeAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -311,7 +311,7 @@ suggestExportUnusedTopBinding srcOpt ParsedModule{pm_parsed_source = L _ HsModul
$ hsmodDecls
, Just pos <- _end . getLocatedRange <$> hsmodExports
, Just needComma <- needsComma source <$> hsmodExports
, let exportName = (if needComma then "," else "") <> printExport exportType name
, let exportName = (if needComma then "," else "") <> printExport exportType name
insertPos = pos {_character = pred $ _character pos}
= [("Export ‘" <> name <> "", [TextEdit (Range insertPos insertPos) exportName])]
| otherwise = []
Expand Down Expand Up @@ -833,19 +833,24 @@ suggestNewImport _ _ _ = []
constructNewImportSuggestions
:: PackageExportsMap -> NotInScope -> Maybe [T.Text] -> [T.Text]
constructNewImportSuggestions exportsMap thingMissing notTheseModules = nubOrd
[ renderNewImport identInfo m
[ suggestion
| (identInfo, m) <- fromMaybe [] $ Map.lookup name exportsMap
, canUseIdent thingMissing identInfo
, m `notElem` fromMaybe [] notTheseModules
, suggestion <- renderNewImport identInfo m
]
where
renderNewImport identInfo m
| Just q <- qual = "import qualified " <> m <> " as " <> q
| otherwise = "import " <> m <> " (" <> importWhat identInfo <> ")"
| Just q <- qual
, asQ <- if q == m then "" else " as " <> q
= ["import qualified " <> m <> asQ]
| otherwise
= ["import " <> m <> " (" <> importWhat identInfo <> ")"
,"import " <> m ]

(qual, name) = case T.splitOn "." (notInScope thingMissing) of
[n] -> (Nothing, n)
segments -> (Just (T.concat $ init segments), last segments)
segments -> (Just (T.intercalate "." $ init segments), last segments)
importWhat IdentInfo {parent, rendered}
| Just p <- parent = p <> "(" <> rendered <> ")"
| otherwise = rendered
Expand Down
5 changes: 5 additions & 0 deletions ghcide/test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1038,17 +1038,22 @@ suggestImportTests = testGroup "suggest import actions"
[ test True [] "f = nonEmpty" [] "import Data.List.NonEmpty (nonEmpty)"
, test True [] "f = (:|)" [] "import Data.List.NonEmpty (NonEmpty((:|)))"
, test True [] "f :: Natural" ["f = undefined"] "import Numeric.Natural (Natural)"
, test True [] "f :: Natural" ["f = undefined"] "import Numeric.Natural"
, test True [] "f :: NonEmpty ()" ["f = () :| []"] "import Data.List.NonEmpty (NonEmpty)"
, test True [] "f :: NonEmpty ()" ["f = () :| []"] "import Data.List.NonEmpty"
, test True [] "f = First" [] "import Data.Monoid (First(First))"
, test True [] "f = Endo" [] "import Data.Monoid (Endo(Endo))"
, test True [] "f = Version" [] "import Data.Version (Version(Version))"
, test True [] "f ExitSuccess = ()" [] "import System.Exit (ExitCode(ExitSuccess))"
, test True [] "f = AssertionFailed" [] "import Control.Exception (AssertionFailed(AssertionFailed))"
, test True ["Prelude"] "f = nonEmpty" [] "import Data.List.NonEmpty (nonEmpty)"
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative (Alternative)"
, test True [] "f :: Alternative f => f ()" ["f = undefined"] "import Control.Applicative"
, test True [] "f = empty" [] "import Control.Applicative (Alternative(empty))"
, test True [] "f = empty" [] "import Control.Applicative"
, test True [] "f = (&)" [] "import Data.Function ((&))"
, test True [] "f = NE.nonEmpty" [] "import qualified Data.List.NonEmpty as NE"
, test True [] "f = Data.List.NonEmpty.nonEmpty" [] "import qualified Data.List.NonEmpty"
, test True [] "f :: Typeable a => a" ["f = undefined"] "import Data.Typeable (Typeable)"
, test True [] "f = pack" [] "import Data.Text (pack)"
, test True [] "f :: Text" ["f = undefined"] "import Data.Text (Text)"
Expand Down

0 comments on commit 050d988

Please sign in to comment.