Skip to content

Commit

Permalink
Abbreviate explicit import code lenses (haskell#2769)
Browse files Browse the repository at this point in the history
* Abbreviate explicit import code lenses

The tests currently don't check anything about the titles, I'm unsure
whether it's worth writing a test just for this.

Fixes haskell#2765.

* Add tests for abbreviation and fix bugs

* Fix a warning
  • Loading branch information
michaelpj authored and July541 committed Mar 29, 2022
1 parent c770fbe commit 4824357
Show file tree
Hide file tree
Showing 2 changed files with 69 additions and 4 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Ide.Plugin.ExplicitImports
, descriptorForModules
, extractMinimalImports
, within
, abbreviateImportTitle
, Log(..)
) where

Expand All @@ -28,6 +29,7 @@ import qualified Data.Map.Strict as Map
import Data.Maybe (catMaybes, fromMaybe,
isJust)
import qualified Data.Text as T
import Data.String (fromString)
import Development.IDE hiding (pluginHandlers,
pluginRules)
import Development.IDE.Core.PositionMapping
Expand Down Expand Up @@ -252,7 +254,6 @@ extractMinimalImports (Just hsc) (Just TcModuleResult {..}) = do
notExported [] _ = True
notExported exports (L _ ImportDecl{ideclName = L _ name}) =
not $ any (\e -> ("module " ++ moduleNameString name) == e) exports
notExported _ _ = False
extractMinimalImports _ _ = return ([], Nothing)

mkExplicitEdit :: (ModuleName -> Bool) -> PositionMapping -> LImportDecl GhcRn -> T.Text -> Maybe TextEdit
Expand All @@ -269,12 +270,19 @@ mkExplicitEdit pred posMapping (L (locA -> src) imp) explicit
| otherwise =
Nothing

-- This number is somewhat arbitrarily chosen. Ideally the protocol would tell us these things,
-- but at the moment I don't believe we know it.
-- 80 columns is traditional, but Haskellers tend to use longer lines (citation needed) and it's
-- probably not too bad if the lens is a *bit* longer than normal lines.
maxColumns :: Int
maxColumns = 120

-- | Given an import declaration, generate a code lens unless it has an
-- explicit import list or it's qualified
generateLens :: PluginId -> Uri -> TextEdit -> IO (Maybe CodeLens)
generateLens pId uri importEdit@TextEdit {_range, _newText} = do
-- The title of the command is just the minimal explicit import decl
let title = _newText
let
title = abbreviateImportTitle _newText
-- the code lens has no extra data
_xdata = Nothing
-- an edit that replaces the whole declaration with the explicit one
Expand All @@ -287,6 +295,38 @@ generateLens pId uri importEdit@TextEdit {_range, _newText} = do
-- create and return the code lens
return $ Just CodeLens {..}

-- | The title of the command is ideally the minimal explicit import decl, but
-- we don't want to create a really massive code lens (and the decl can be extremely large!).
-- So we abbreviate it to fit a max column size, and indicate how many more items are in the list
-- after the abbreviation
abbreviateImportTitle :: T.Text -> T.Text
abbreviateImportTitle input =
let
-- For starters, we only want one line in the title
oneLineText = T.unwords $ T.lines input
-- Now, split at the max columns, leaving space for the summary text we're going to add
-- (conservatively assuming we won't need to print a number larger than 100)
(prefix, suffix) = T.splitAt (maxColumns - (T.length (summaryText 100))) oneLineText
-- We also want to truncate the last item so we get a "clean" break, rather than half way through
-- something. The conditional here is just because 'breakOnEnd' doesn't give us quite the right thing
-- if there are actually no commas.
(actualPrefix, extraSuffix) = if T.count "," prefix > 0 then T.breakOnEnd "," prefix else (prefix, "")
actualSuffix = extraSuffix <> suffix

-- The number of additional items is the number of commas+1
numAdditionalItems = T.count "," actualSuffix + 1
-- We want to make text like this: import Foo (AImport, BImport, ... (30 items))
-- We also want it to look sensible if we end up splitting in the module name itself,
summaryText n = " ... (" <> fromString (show n) <> " items)"
-- so we only add a trailing paren if we've split in the export list
suffixText = summaryText numAdditionalItems <> if T.count "(" prefix > 0 then ")" else ""
title =
-- If the original text fits, just use it
if T.length oneLineText <= maxColumns
then oneLineText
else actualPrefix <> suffixText
in title

--------------------------------------------------------------------------------

-- | A helper to run ide actions
Expand Down
27 changes: 26 additions & 1 deletion plugins/hls-explicit-imports-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,13 @@ import Test.Hls
explicitImportsPlugin :: PluginDescriptor IdeState
explicitImportsPlugin = ExplicitImports.descriptor mempty "explicitImports"

longModule :: T.Text
longModule = "F" <> T.replicate 80 "o"

main :: IO ()
main = defaultTestRunner $
testGroup
"Refine Imports"
"Make imports explicit"
[ codeActionGoldenTest "UsualCase" 3 0
, codeLensGoldenTest "UsualCase" 0
, testCase "No CodeAction when exported" $
Expand All @@ -35,6 +37,29 @@ main = defaultTestRunner $
doc <- openDoc "Exported.hs" "haskell"
lenses <- getCodeLenses doc
liftIO $ lenses @?= []
, testGroup "Title abbreviation"
[ testCase "not abbreviated" $
let i = "import " <> T.replicate 70 "F" <> " (Athing, Bthing, Cthing)"
in ExplicitImports.abbreviateImportTitle i @?= i
, testCase "abbreviated in module name" $
let i = "import " <> T.replicate 120 "F" <> " (Athing, Bthing, Cthing)"
o = "import " <> T.replicate 97 "F" <> " ... (3 items)"
in ExplicitImports.abbreviateImportTitle i @?= o
, testCase "abbreviated in import list" $
let i = "import " <> T.replicate 78 "F" <> " (Athing, Bthing, Cthing, Dthing, Ething)"
o = "import " <> T.replicate 78 "F" <> " (Athing, Bthing, ... (3 items))"
in ExplicitImports.abbreviateImportTitle i @?= o
-- This one breaks earlier in the same import item, but still splits the list in the same place
, testCase "abbreviated in import list (slightly shorter module)" $
let i = "import " <> T.replicate 76 "F" <> " (Athing, Bthing, Cthing, Dthing, Ething)"
o = "import " <> T.replicate 76 "F" <> " (Athing, Bthing, ... (3 items))"
in ExplicitImports.abbreviateImportTitle i @?= o
-- This one breaks later in the same import item, but still splits the list in the same place
, testCase "abbreviated in import list (slightly longer module)" $
let i = "import " <> T.replicate 80 "F" <> " (Athing, Bthing, Cthing, Dthing, Ething)"
o = "import " <> T.replicate 80 "F" <> " (Athing, Bthing, ... (3 items))"
in ExplicitImports.abbreviateImportTitle i @?= o
]
]

-- code action tests
Expand Down

0 comments on commit 4824357

Please sign in to comment.