Skip to content

Commit fc38659

Browse files
committed
Move brittany plugin from HIE
1 parent 7d42115 commit fc38659

File tree

3 files changed

+117
-2
lines changed

3 files changed

+117
-2
lines changed

exe/Main.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,7 @@ import Ide.Plugin.Example2 as Example2
9292
import Ide.Plugin.GhcIde as GhcIde
9393
import Ide.Plugin.Floskell as Floskell
9494
import Ide.Plugin.Ormolu as Ormolu
95+
import Ide.Plugin.Brittany as Brittany
9596
import Ide.Plugin.Pragmas as Pragmas
9697

9798

@@ -113,13 +114,13 @@ idePlugins includeExamples = pluginDescToIdePlugins allPlugins
113114
basePlugins =
114115
[
115116
-- applyRefactDescriptor "applyrefact"
116-
-- , brittanyDescriptor "brittany"
117+
Brittany.descriptor "brittany"
117118
-- , haddockDescriptor "haddock"
118119
-- , hareDescriptor "hare"
119120
-- , hsimportDescriptor "hsimport"
120121
-- , liquidDescriptor "liquid"
121122
-- , packageDescriptor "package"
122-
GhcIde.descriptor "ghcide"
123+
, GhcIde.descriptor "ghcide"
123124
, Pragmas.descriptor "pragmas"
124125
, Floskell.descriptor "floskell"
125126
-- , genericDescriptor "generic"

haskell-language-server.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ library
3030
Ide.Cradle
3131
Ide.Logger
3232
Ide.Plugin
33+
Ide.Plugin.Brittany
3334
Ide.Plugin.Config
3435
Ide.Plugin.Example
3536
Ide.Plugin.Example2
@@ -48,6 +49,7 @@ library
4849
base >=4.7 && <5
4950
, aeson
5051
, binary
52+
, brittany
5153
, bytestring
5254
, Cabal
5355
, cabal-helper >= 1.0

src/Ide/Plugin/Brittany.hs

Lines changed: 112 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,112 @@
1+
module Ide.Plugin.Brittany where
2+
3+
import Control.Lens
4+
import Control.Monad.IO.Class
5+
import Control.Monad.Trans.Maybe (MaybeT, runMaybeT)
6+
import Data.Coerce
7+
import Data.Semigroup
8+
import Data.Text (Text)
9+
import qualified Data.Text as T
10+
import Development.IDE.Types.Location
11+
import Language.Haskell.Brittany
12+
import Language.Haskell.LSP.Types as J
13+
import qualified Language.Haskell.LSP.Types.Lens as J
14+
import Ide.Plugin.Formatter
15+
import Ide.Types
16+
17+
import System.FilePath
18+
import Data.Maybe (maybeToList)
19+
20+
descriptor :: PluginId -> PluginDescriptor
21+
descriptor plId = PluginDescriptor
22+
{ pluginId = plId
23+
, pluginRules = mempty
24+
, pluginCommands = []
25+
, pluginCodeActionProvider = Nothing
26+
, pluginCodeLensProvider = Nothing
27+
, pluginDiagnosticProvider = Nothing
28+
, pluginHoverProvider = Nothing
29+
, pluginSymbolsProvider = Nothing
30+
, pluginFormattingProvider = Just provider
31+
, pluginCompletionProvider = Nothing
32+
}
33+
34+
-- | Formatter provider of Brittany.
35+
-- Formats the given source in either a given Range or the whole Document.
36+
-- If the provider fails an error is returned that can be displayed to the user.
37+
provider
38+
:: FormattingProvider IO
39+
provider _ideState typ contents fp opts = do
40+
-- text uri formatType opts = pluginGetFile "brittanyCmd: " uri $ \fp -> do
41+
confFile <- liftIO $ getConfFile fp
42+
let (range, selectedContents) = case typ of
43+
FormatText -> (fullRange contents, contents)
44+
FormatRange r -> (normalize r, extractRange r contents)
45+
46+
res <- formatText confFile opts selectedContents
47+
case res of
48+
Left err -> return $ Left $ responseError (T.pack $ "brittanyCmd: " ++ unlines (map showErr err))
49+
Right newText -> return $ Right $ J.List [TextEdit range newText]
50+
51+
-- | Primitive to format text with the given option.
52+
-- May not throw exceptions but return a Left value.
53+
-- Errors may be presented to the user.
54+
formatText
55+
:: MonadIO m
56+
=> Maybe FilePath -- ^ Path to configs. If Nothing, default configs will be used.
57+
-> FormattingOptions -- ^ Options for the formatter such as indentation.
58+
-> Text -- ^ Text to format
59+
-> m (Either [BrittanyError] Text) -- ^ Either formatted Text or a error from Brittany.
60+
formatText confFile opts text =
61+
liftIO $ runBrittany tabSize confFile text
62+
where tabSize = opts ^. J.tabSize
63+
64+
-- | Extend to the line below and above to replace newline character.
65+
normalize :: Range -> Range
66+
normalize (Range (Position sl _) (Position el _)) =
67+
Range (Position sl 0) (Position (el + 1) 0)
68+
69+
-- | Recursively search in every directory of the given filepath for brittany.yaml.
70+
-- If no such file has been found, return Nothing.
71+
getConfFile :: NormalizedFilePath -> IO (Maybe FilePath)
72+
getConfFile = findLocalConfigPath . takeDirectory . fromNormalizedFilePath
73+
74+
-- | Run Brittany on the given text with the given tab size and
75+
-- a configuration path. If no configuration path is given, a
76+
-- default configuration is chosen. The configuration may overwrite
77+
-- tab size parameter.
78+
--
79+
-- Returns either a list of Brittany Errors or the reformatted text.
80+
-- May not throw an exception.
81+
runBrittany :: Int -- ^ tab size
82+
-> Maybe FilePath -- ^ local config file
83+
-> Text -- ^ text to format
84+
-> IO (Either [BrittanyError] Text)
85+
runBrittany tabSize confPath text = do
86+
let cfg = mempty
87+
{ _conf_layout =
88+
mempty { _lconfig_indentAmount = opt (coerce tabSize)
89+
}
90+
, _conf_forward =
91+
(mempty :: CForwardOptions Option)
92+
{ _options_ghc = opt (runIdentity ( _options_ghc forwardOptionsSyntaxExtsEnabled))
93+
}
94+
}
95+
96+
config <- fromMaybeT (pure staticDefaultConfig) (readConfigsWithUserConfig cfg (maybeToList confPath))
97+
parsePrintModule config text
98+
99+
fromMaybeT :: Monad m => m a -> MaybeT m a -> m a
100+
fromMaybeT def act = runMaybeT act >>= maybe def return
101+
102+
opt :: a -> Option a
103+
opt = Option . Just
104+
105+
showErr :: BrittanyError -> String
106+
showErr (ErrorInput s) = s
107+
showErr (ErrorMacroConfig err input)
108+
= "Error: parse error in inline configuration: " ++ err ++ " in the string \"" ++ input ++ "\"."
109+
showErr (ErrorUnusedComment s) = s
110+
showErr (LayoutWarning s) = s
111+
showErr (ErrorUnknownNode s _) = s
112+
showErr ErrorOutputCheck = "Brittany error - invalid output"

0 commit comments

Comments
 (0)