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

Commit 0af5c3e

Browse files
committed
Execute formatter provider
Implement Cmds for floskell and brittany to format text. Make it callable for other plugins.
1 parent a6d9107 commit 0af5c3e

File tree

4 files changed

+146
-75
lines changed

4 files changed

+146
-75
lines changed

hie-plugin-api/Haskell/Ide/Engine/PluginsIdeMonads.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,7 @@ module Haskell.Ide.Engine.PluginsIdeMonads
7575
, PublishDiagnosticsParams(..)
7676
, List(..)
7777
, FormattingOptions(..)
78+
, FormatTextCmdParams(..)
7879
)
7980
where
8081

@@ -208,6 +209,16 @@ type HoverProvider = Uri -> Position -> IdeM (IdeResult [Hover])
208209

209210
type SymbolProvider = Uri -> IdeDeferM (IdeResult [DocumentSymbol])
210211

212+
-- | Format Paramaters for Cmd.
213+
-- Can be used to send messages to formatters
214+
data FormatTextCmdParams = FormatTextCmdParams
215+
{ fmtText :: T.Text -- ^ Text to format
216+
, fmtResultRange :: Range -- ^ Range where the text will be inserted.
217+
, fmtTextOptions :: FormattingOptions -- ^ Options for the formatter
218+
}
219+
deriving (Eq, Show, Generic, FromJSON, ToJSON)
220+
221+
211222
-- | Format the document either as a whole or only a given Range of it.
212223
data FormattingType = FormatDocument
213224
| FormatRange Range

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

Lines changed: 67 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -25,14 +25,17 @@ data FormatParams = FormatParams Int Uri (Maybe Range)
2525

2626
brittanyDescriptor :: PluginId -> PluginDescriptor
2727
brittanyDescriptor plId = PluginDescriptor
28-
{ pluginId = plId
29-
, pluginName = "Brittany"
30-
, pluginDesc = "Brittany is a tool to format source code."
31-
, pluginCommands = [PluginCommand "format" "Format the document" formatCmd]
28+
{ pluginId = plId
29+
, pluginName = "Brittany"
30+
, pluginDesc = "Brittany is a tool to format source code."
31+
, pluginCommands = [ PluginCommand "formatText"
32+
"Format the given Text with Brittany"
33+
formatCmd
34+
]
3235
, pluginCodeActionProvider = Nothing
3336
, pluginDiagnosticProvider = Nothing
34-
, pluginHoverProvider = Nothing
35-
, pluginSymbolProvider = Nothing
37+
, pluginHoverProvider = Nothing
38+
, pluginSymbolProvider = Nothing
3639
, pluginFormattingProvider = Just provider
3740
}
3841

@@ -45,51 +48,71 @@ provider = format
4548
-- |Formatter of Brittany.
4649
-- Formats the given source in either a given Range or the whole Document.
4750
-- If the provider fails an error is returned that can be displayed to the user.
48-
format :: (MonadIO m, MonadIde m)
49-
=> Uri
50-
-> FormattingType
51-
-> FormattingOptions
52-
-> m (IdeResult [TextEdit])
51+
format
52+
:: (MonadIO m, MonadIde m)
53+
=> Uri
54+
-> FormattingType
55+
-> FormattingOptions
56+
-> m (IdeResult [TextEdit])
5357
format uri formatType opts = pluginGetFile "brittanyCmd: " uri $ \fp -> do
5458
confFile <- liftIO $ getConfFile fp
55-
mtext <- readVFS uri
59+
mtext <- readVFS uri
5660
case mtext of
57-
Nothing -> return
58-
$ IdeResultFail (IdeError InternalError "File was not open" Null)
59-
Just text -> case formatType of
60-
FormatRange r -> do
61-
res <- liftIO $ runBrittany tabSize confFile $ extractRange r text
62-
case res of
63-
Left err -> return
64-
$ IdeResultFail
65-
(IdeError
66-
PluginError
67-
(T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
68-
Null)
69-
Right newText -> do
70-
let textEdit = J.TextEdit (normalize r) newText
71-
return $ IdeResultOk [textEdit]
72-
FormatDocument -> do
73-
res <- liftIO $ runBrittany tabSize confFile text
74-
case res of
75-
Left err -> return
76-
$ IdeResultFail
77-
(IdeError
78-
PluginError
79-
(T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
80-
Null)
81-
Right newText -> return
82-
$ IdeResultOk [J.TextEdit (fullRange text) newText]
83-
where
84-
tabSize = opts ^. J.tabSize
61+
-- Uri could not be read from the virtual file system.
62+
Nothing ->
63+
return $ IdeResultFail (IdeError InternalError "File was not open" Null)
64+
Just text -> do
65+
let (range, selectedContents) = case formatType of
66+
FormatDocument -> (fullRange text, text)
67+
FormatRange r -> (normalize r, extractRange r text)
68+
69+
res <- formatText confFile opts selectedContents
70+
case res of
71+
Left err -> return $ IdeResultFail
72+
(IdeError PluginError
73+
(T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
74+
Null
75+
)
76+
Right newText -> do
77+
let textEdit = J.TextEdit range newText
78+
return $ IdeResultOk [textEdit]
79+
80+
-- | Primitive to format text with the given option.
81+
-- May not throw exceptions but return a Left value.
82+
-- Errors may be presented to the user.
83+
formatText
84+
:: MonadIO m
85+
=> Maybe FilePath -- ^ Path to configs. If Nothing, default configs will be used.
86+
-> FormattingOptions -- ^ Options for the formatter such as indentation.
87+
-> Text -- ^ Text to format
88+
-> m (Either [BrittanyError] Text) -- ^ Either formatted Text or a error from Brittany.
89+
formatText confFile opts text =
90+
liftIO $ runBrittany tabSize confFile text
91+
where tabSize = opts ^. J.tabSize
8592

8693
-- | Format a source with the given options.
8794
-- Synchronized command.
8895
-- Other plugins can use this Command it to execute formatters.
89-
-- Command can be run by ``
90-
formatCmd :: CommandFunc FormatCmdParams [TextEdit]
91-
formatCmd = CmdSync $ \fmtParam ->
92-
format (fmtUri fmtParam) (fmtType fmtParam) (fmtOptions fmtParam)
96+
-- Command can be run by
97+
-- ```
98+
-- runPluginCommand
99+
-- (pluginId plugin)
100+
-- "formatText"
101+
-- (dynToJSON $ toDynJSON $ FormatTextCmdParams t r (FormattingOptions 2 True))
102+
-- ```
103+
formatCmd :: CommandFunc FormatTextCmdParams [TextEdit]
104+
formatCmd = CmdSync $ \(FormatTextCmdParams text fmtRange fmtOpts) -> do
105+
rootPath <- getRootPath
106+
textEdit <- formatText rootPath fmtOpts text
107+
case textEdit of
108+
Left err -> return $ IdeResultFail
109+
(IdeError PluginError
110+
(T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
111+
Null
112+
)
113+
Right newText -> do
114+
let edit = J.TextEdit fmtRange newText
115+
return $ IdeResultOk [edit]
93116

94117
-- | Extend to the line below to replace newline character, as above.
95118
normalize :: Range -> Range

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

Lines changed: 29 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,16 +10,21 @@ import Data.Aeson (Value (Null))
1010
import qualified Data.ByteString.Lazy as BS
1111
import qualified Data.Text as T
1212
import qualified Data.Text.Encoding as T
13+
import Data.Maybe
1314
import Floskell
1415
import Haskell.Ide.Engine.MonadTypes
1516
import Haskell.Ide.Engine.PluginUtils
17+
import qualified Language.Haskell.LSP.Types as J
1618

1719
floskellDescriptor :: PluginId -> PluginDescriptor
1820
floskellDescriptor plId = PluginDescriptor
1921
{ pluginId = plId
2022
, pluginName = "Floskell"
2123
, pluginDesc = "A flexible Haskell source code pretty printer."
22-
, pluginCommands = []
24+
, pluginCommands = [ PluginCommand "formatText"
25+
"Format the given Text with Floskell"
26+
formatCmd
27+
]
2328
, pluginCodeActionProvider = Nothing
2429
, pluginDiagnosticProvider = Nothing
2530
, pluginHoverProvider = Nothing
@@ -43,9 +48,31 @@ provider uri typ _opts =
4348
FormatRange r -> (r, extractRange r contents)
4449
result = reformat config (uriToFilePath uri) (BS.fromStrict (T.encodeUtf8 selectedContents))
4550
in case result of
46-
Left err -> return $ IdeResultFail (IdeError PluginError (T.pack err) Null)
51+
Left err -> return $ IdeResultFail (IdeError PluginError (T.pack $ "floskellCmd: " ++ err) Null)
4752
Right new -> return $ IdeResultOk [TextEdit range (T.decodeUtf8 (BS.toStrict new))]
4853

54+
-- | Format a source with the given options.
55+
-- Synchronized command.
56+
-- Other plugins can use this Command it to execute formatters.
57+
-- Command can be run by
58+
-- ```
59+
-- runPluginCommand
60+
-- (pluginId plugin)
61+
-- "formatText"
62+
-- (dynToJSON $ toDynJSON $ FormatTextCmdParams t r (FormattingOptions 2 True))
63+
-- ```
64+
formatCmd :: CommandFunc FormatTextCmdParams [TextEdit]
65+
formatCmd = CmdSync $ \(FormatTextCmdParams text fmtRange _) -> do
66+
rootPath <- getRootPath
67+
config <- liftIO $ findConfigOrDefault (fromMaybe "" rootPath)
68+
let textEdit = reformat config Nothing (BS.fromStrict (T.encodeUtf8 text))
69+
case textEdit of
70+
Left err -> return $ IdeResultFail
71+
(IdeError PluginError (T.pack $ "floskellCmd: " ++ err) Null)
72+
Right newText -> do
73+
let edit = J.TextEdit fmtRange (T.decodeUtf8 (BS.toStrict newText))
74+
return $ IdeResultOk [edit]
75+
4976
-- | Find Floskell Config, user and system wide or provides a default style.
5077
-- Every directory of the filepath will be searched to find a user configuration.
5178
-- Also looks into places such as XDG_CONFIG_DIRECTORY<https://specifications.freedesktop.org/basedir-spec/basedir-spec-latest.html>.

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

Lines changed: 39 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ import Control.Monad
1010
import Data.Aeson
1111
import Data.Bitraversable
1212
import Data.Bifunctor
13-
import Data.Either
1413
import Data.Foldable
1514
import Data.Maybe
1615
import Data.Monoid ( (<>) )
@@ -25,8 +24,6 @@ import qualified Haskell.Ide.Engine.Support.HieExtras as Hie
2524
import qualified Language.Haskell.LSP.Types as J
2625
import qualified Language.Haskell.LSP.Types.Lens as J
2726
import Haskell.Ide.Engine.PluginUtils
28-
import qualified Haskell.Ide.Engine.Plugin.Brittany
29-
as Brittany
3027
import qualified Haskell.Ide.Engine.Plugin.Hoogle
3128
as Hoogle
3229
import System.Directory
@@ -55,12 +52,10 @@ importCmd :: CommandFunc ImportParams J.WorkspaceEdit
5552
importCmd = CmdSync $ \(ImportParams uri modName) -> importModule uri modName
5653

5754
importModule :: Uri -> T.Text -> IdeGhcM (IdeResult J.WorkspaceEdit)
58-
importModule uri modName =
59-
pluginGetFile "hsimport cmd: " uri $ \origInput -> do
60-
55+
importModule uri modName = pluginGetFile "hsimport cmd: " uri $ \origInput -> do
6156
shouldFormat <- formatOnImportOn <$> getConfig
6257

63-
fileMap <- GM.mkRevRedirMapFunc
58+
fileMap <- GM.mkRevRedirMapFunc
6459
GM.withMappedFile origInput $ \input -> do
6560

6661
tmpDir <- liftIO getTemporaryDirectory
@@ -80,36 +75,51 @@ importModule uri modName =
8075
Nothing -> do
8176
newText <- liftIO $ T.readFile output
8277
liftIO $ removeFile output
83-
J.WorkspaceEdit mChanges mDocChanges <- liftToGhc $ makeDiffResult input newText fileMap
78+
J.WorkspaceEdit mChanges mDocChanges <- liftToGhc
79+
$ makeDiffResult input newText fileMap
8480

8581
if shouldFormat
8682
then do
87-
config <- getConfig
83+
config <- getConfig
8884
plugins <- getPlugins
8985
let mprovider = Hie.getFormattingPlugin config plugins
90-
case mprovider of
91-
Nothing -> return $ IdeResultOk (J.WorkspaceEdit mChanges mDocChanges)
92-
Just (plugin, _) -> do
93-
let fmtCmd = J.Command "unused"
94-
results <- forM mChanges $ mapM $ mapM $ (runPluginCommand (pluginId plugin) "format" . dynToJSON . toDynJSON)
95-
86+
case mprovider of
87+
Nothing ->
88+
return $ IdeResultOk (J.WorkspaceEdit mChanges mDocChanges)
9689

97-
98-
-- -- Format the import with Brittany
99-
-- confFile <- liftIO $ Brittany.getConfFile origInput
100-
-- newChanges <- forM mChanges $ mapM $ mapM (formatTextEdit confFile)
101-
-- newDocChanges <- forM mDocChanges $ mapM $ \(J.TextDocumentEdit vDocId tes) -> do
102-
-- ftes <- forM tes (formatTextEdit confFile)
103-
-- return (J.TextDocumentEdit vDocId ftes)
104-
105-
return $ IdeResultOk (J.WorkspaceEdit mChanges mDocChanges) -- (J.WorkspaceEdit newChanges newDocChanges)
106-
else
90+
Just (plugin, _) -> do
91+
newChanges <- forM mChanges $ \change -> do
92+
let func = mapM (formatTextEdit plugin)
93+
res <- mapM func change
94+
return $ fmap flatten res
95+
96+
newDocChanges <- forM mDocChanges $ \change -> do
97+
let cmd (J.TextDocumentEdit vids edits) = do
98+
newEdits <- mapM (formatTextEdit plugin) edits
99+
return $ J.TextDocumentEdit vids (flatten newEdits)
100+
mapM cmd change
101+
102+
return $ IdeResultOk
103+
(J.WorkspaceEdit newChanges
104+
newDocChanges
105+
)
106+
else
107107
return $ IdeResultOk (J.WorkspaceEdit mChanges mDocChanges)
108108

109-
where formatTextEdit confFile (J.TextEdit r t) = do
110-
-- TODO: This tab size of 2 spaces should probably be taken from a config
111-
ft <- fromRight t <$> liftIO (Brittany.runBrittany 2 confFile t)
112-
return (J.TextEdit r ft)
109+
where
110+
flatten :: List [a] -> List a
111+
flatten (J.List list) = J.List (join list)
112+
113+
formatTextEdit :: PluginDescriptor -> J.TextEdit -> IdeGhcM [J.TextEdit]
114+
formatTextEdit plugin edit@(J.TextEdit r t) = do
115+
result <- runPluginCommand
116+
(pluginId plugin)
117+
"formatText"
118+
-- TODO: should this be in the configs?
119+
(dynToJSON $ toDynJSON $ FormatTextCmdParams t r (FormattingOptions 2 True))
120+
return $ case result of
121+
IdeResultOk e -> fromMaybe [edit] (fromDynJSON e)
122+
_ -> [edit]
113123

114124
codeActionProvider :: CodeActionProvider
115125
codeActionProvider plId docId _ context = do

0 commit comments

Comments
 (0)