1- {-# LANGUAGE DeriveAnyClass #-}
2- {-# LANGUAGE DeriveGeneric #-}
31{-# LANGUAGE OverloadedStrings #-}
42module Haskell.Ide.Engine.Plugin.Brittany where
53
@@ -11,7 +9,6 @@ import Data.Coerce
119import Data.Semigroup
1210import Data.Text (Text )
1311import qualified Data.Text as T
14- import GHC.Generics
1512import Haskell.Ide.Engine.MonadTypes
1613import Haskell.Ide.Engine.PluginUtils
1714import Language.Haskell.Brittany
@@ -20,52 +17,62 @@ import qualified Language.Haskell.LSP.Types.Lens as J
2017import System.FilePath (FilePath , takeDirectory )
2118import Data.Maybe (maybeToList )
2219
23- data FormatParams = FormatParams Int Uri (Maybe Range )
24- deriving (Eq , Show , Generic , FromJSON , ToJSON )
25-
2620brittanyDescriptor :: PluginId -> PluginDescriptor
2721brittanyDescriptor plId = PluginDescriptor
28- { pluginId = plId
29- , pluginName = " Brittany"
30- , pluginDesc = " Brittany is a tool to format source code."
31- , pluginCommands = []
22+ { pluginId = plId
23+ , pluginName = " Brittany"
24+ , pluginDesc = " Brittany is a tool to format source code."
25+ , pluginCommands = []
3226 , pluginCodeActionProvider = Nothing
3327 , pluginDiagnosticProvider = Nothing
34- , pluginHoverProvider = Nothing
35- , pluginSymbolProvider = Nothing
28+ , pluginHoverProvider = Nothing
29+ , pluginSymbolProvider = Nothing
3630 , pluginFormattingProvider = Just provider
3731 }
3832
3933-- | Formatter provider of Brittany.
4034-- Formats the given source in either a given Range or the whole Document.
4135-- If the provider fails an error is returned that can be displayed to the user.
42- provider :: FormattingProvider
43- provider uri formatType opts = pluginGetFile " brittanyCmd: " uri $ \ file -> do
44- confFile <- liftIO $ getConfFile file
45- mtext <- readVFS uri
46- case mtext of
47- Nothing -> return $ IdeResultFail (IdeError InternalError " File was not open" Null )
48- Just text -> case formatType of
49- FormatRange r -> do
50- res <- liftIO $ runBrittany tabSize confFile $ extractRange r text
51- case res of
52- Left err -> return $ IdeResultFail (IdeError PluginError
53- (T. pack $ " brittanyCmd: " ++ unlines (map showErr err)) Null )
54- Right newText -> do
55- let textEdit = J. TextEdit (normalize r) newText
56- return $ IdeResultOk [textEdit]
57- FormatDocument -> do
58- res <- liftIO $ runBrittany tabSize confFile text
59- case res of
60- Left err -> return $ IdeResultFail (IdeError PluginError
61- (T. pack $ " brittanyCmd: " ++ unlines (map showErr err)) Null )
62- Right newText ->
63- return $ IdeResultOk [J. TextEdit (fullRange text) newText]
36+ provider
37+ :: MonadIO m
38+ => Text
39+ -> Uri
40+ -> FormattingType
41+ -> FormattingOptions
42+ -> m (IdeResult [TextEdit ])
43+ provider text uri formatType opts = pluginGetFile " brittanyCmd: " uri $ \ fp -> do
44+ confFile <- liftIO $ getConfFile fp
45+ let (range, selectedContents) = case formatType of
46+ FormatDocument -> (fullRange text, text)
47+ FormatRange r -> (normalize r, extractRange r text)
48+
49+ res <- formatText confFile opts selectedContents
50+ case res of
51+ Left err -> return $ IdeResultFail
52+ (IdeError PluginError
53+ (T. pack $ " brittanyCmd: " ++ unlines (map showErr err))
54+ Null
55+ )
56+ Right newText -> do
57+ let textEdit = J. TextEdit range newText
58+ return $ IdeResultOk [textEdit]
59+
60+ -- | Primitive to format text with the given option.
61+ -- May not throw exceptions but return a Left value.
62+ -- Errors may be presented to the user.
63+ formatText
64+ :: MonadIO m
65+ => Maybe FilePath -- ^ Path to configs. If Nothing, default configs will be used.
66+ -> FormattingOptions -- ^ Options for the formatter such as indentation.
67+ -> Text -- ^ Text to format
68+ -> m (Either [BrittanyError ] Text ) -- ^ Either formatted Text or a error from Brittany.
69+ formatText confFile opts text =
70+ liftIO $ runBrittany tabSize confFile text
6471 where tabSize = opts ^. J. tabSize
6572
73+ -- | Extend to the line below to replace newline character, as above.
6674normalize :: Range -> Range
6775normalize (Range (Position sl _) (Position el _)) =
68- -- Extend to the line below to replace newline character, as above
6976 Range (Position sl 0 ) (Position (el + 1 ) 0 )
7077
7178-- | Recursively search in every directory of the given filepath for brittany.yaml
0 commit comments