Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit d6dedd3

Browse files
committed
Fix additional newline when Brittany uses import-list
1 parent 85ac6e4 commit d6dedd3

File tree

1 file changed

+32
-10
lines changed

1 file changed

+32
-10
lines changed

src/Haskell/Ide/Engine/Plugin/HsImport.hs

+32-10
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE DeriveGeneric #-}
33
{-# LANGUAGE DeriveAnyClass #-}
44
{-# LANGUAGE TupleSections #-}
5+
{-# LANGUAGE LambdaCase #-}
56
module Haskell.Ide.Engine.Plugin.HsImport where
67

78
import Control.Lens.Operators
@@ -72,7 +73,6 @@ importModule uri importList modName =
7273
tmpDir <- liftIO getTemporaryDirectory
7374
(output, outputH) <- liftIO $ openTempFile tmpDir "hsimportOutput"
7475
liftIO $ hClose outputH
75-
7676
let args = defaultArgs { moduleName = T.unpack modName
7777
, inputSrcFile = input
7878
, symbolName = T.unpack $ fromMaybe "" importList
@@ -107,16 +107,38 @@ importModule uri importList modName =
107107
return $ IdeResultOk (J.WorkspaceEdit mChanges mDocChanges)
108108

109109
Just (_, provider) -> do
110-
let formatEdit :: J.TextEdit -> IdeGhcM J.TextEdit
110+
let
111+
-- | Dirty little hack.
112+
-- Necessary in the following case:
113+
-- We want to add an item to an existing import-list.
114+
-- The diff algorithm does not count the newline character
115+
-- as part of the diff between new and old text.
116+
-- However, some formatters (Brittany), add a trailing
117+
-- newline nevertheless.
118+
-- This leads to the problem that an additional
119+
-- newline is inserted into the source.
120+
-- This function makes sure, that if the original text
121+
-- did not have a newline, none will be added, assuming
122+
-- that the diff algorithm continues to not count newlines
123+
-- as part of the diff.
124+
-- This is only save to do in this very specific environment.
125+
-- In any other case, this function may not be copy-pasted
126+
-- to solve a similar problem.
127+
renormalise :: T.Text -> T.Text -> T.Text
128+
renormalise orig formatted
129+
| T.null orig || T.null formatted = orig <> formatted
130+
| T.last orig /= '\n' && T.last formatted == '\n' = T.init formatted
131+
| otherwise = formatted
132+
133+
formatEdit :: J.TextEdit -> IdeGhcM J.TextEdit
111134
formatEdit origEdit@(J.TextEdit r t) = do
112135
-- TODO: are these default FormattingOptions ok?
113-
res <- liftToGhc $ provider t uri FormatText (FormattingOptions 2 True)
114-
let formatEdits = case res of
115-
IdeResultOk xs -> xs
116-
_ -> [origEdit]
136+
formatEdits <-
137+
liftToGhc $ provider t uri FormatText (FormattingOptions 2 True) >>= \case
138+
IdeResultOk xs -> return xs
139+
_ -> return [origEdit]
117140
-- let edits = foldl' J.editTextEdit origEdit formatEdits -- TODO: this seems broken.
118-
-- liftIO $ hPutStrLn stderr $ "Text Edits: " ++ show formatEdits
119-
return (J.TextEdit r (J._newText $ head formatEdits))
141+
return (J.TextEdit r (renormalise t . J._newText $ head formatEdits))
120142

121143
-- behold: the legendary triple mapM
122144
newChanges <- (mapM . mapM . mapM) formatEdit mChanges
@@ -186,7 +208,7 @@ codeActionProvider plId docId _ context = do
186208
applySearchStyle Exact term = "is:exact " <> term
187209
applySearchStyle ExactName term = case T.words term of
188210
[] -> term
189-
(x:_) -> "is:exact " <> x
211+
(x : _) -> "is:exact " <> x
190212
applySearchStyle (Relax relax) term = relax term
191213

192214
-- | Turn a search term with function name into Import Actions.
@@ -206,7 +228,7 @@ codeActionProvider plId docId _ context = do
206228
termToActions style functionName (diagnostic, termName) = do
207229
let useImportList = case style of
208230
Relax _ -> Nothing
209-
_ -> Just (mkImportAction (Just functionName) diagnostic termName)
231+
_ -> Just (mkImportAction (Just functionName) diagnostic termName)
210232
catMaybes <$> sequenceA
211233
(mkImportAction Nothing diagnostic termName : maybeToList useImportList)
212234

0 commit comments

Comments
 (0)