First pass at Floskell and formatterProvider

This commit is contained in:
Luke Lau 2019-02-09 18:37:19 +00:00
parent 7dd6fd7ab2
commit 3e21f2c091
38 changed files with 165 additions and 40 deletions

3
.gitmodules vendored
View File

@ -32,3 +32,6 @@
url = https://github.com/alanz/ghc-mod.git
[submodule "submodules/floskell"]
path = submodules/floskell
url = https://github.com/bubba/floskell

View File

@ -36,6 +36,7 @@ import Haskell.Ide.Engine.Plugin.HsImport
import Haskell.Ide.Engine.Plugin.Liquid
import Haskell.Ide.Engine.Plugin.Package
import Haskell.Ide.Engine.Plugin.Pragmas
import Haskell.Ide.Engine.Plugin.Floskell
-- ---------------------------------------------------------------------
@ -59,6 +60,7 @@ plugins includeExamples = pluginDescToIdePlugins allPlugins
, liquidDescriptor "liquid"
, packageDescriptor "package"
, pragmasDescriptor "pragmas"
, floskellDescriptor "floskell"
]
examplePlugins =
[example2Descriptor "eg2"

View File

@ -7,3 +7,4 @@ packages:
./submodules/cabal-helper/
./submodules/ghc-mod/
./submodules/ghc-mod/core/
./submodules/floskell

View File

@ -29,6 +29,7 @@ library
Haskell.Ide.Engine.Plugin.Brittany
Haskell.Ide.Engine.Plugin.Build
Haskell.Ide.Engine.Plugin.Example2
Haskell.Ide.Engine.Plugin.Floskell
Haskell.Ide.Engine.Plugin.Fuzzy
Haskell.Ide.Engine.Plugin.GhcMod
Haskell.Ide.Engine.Plugin.HaRe
@ -60,6 +61,7 @@ library
, data-default
, directory
, filepath
, floskell
, fold-debounce
, ghc >= 8.0.1
, ghc-exactprint
@ -96,6 +98,7 @@ library
if flag(pedantic)
ghc-options: -Werror
default-language: Haskell2010
mixins: floskell (Floskell as FloskellFloskell)
executable hie
hs-source-dirs: app

View File

@ -26,6 +26,7 @@ data Config =
, liquidOn :: Bool
, completionSnippetsOn :: Bool
, formatOnImportOn :: Bool
, formattingProvider :: T.Text
} deriving (Show,Eq)
instance Default Config where
@ -36,6 +37,7 @@ instance Default Config where
, liquidOn = False
, completionSnippetsOn = True
, formatOnImportOn = True
, formattingProvider = "brittany"
}
-- TODO: Add API for plugins to expose their own LSP config options
@ -49,6 +51,7 @@ instance FromJSON Config where
<*> o .:? "liquidOn" .!= liquidOn def
<*> o .:? "completionSnippetsOn" .!= completionSnippetsOn def
<*> o .:? "formatOnImportOn" .!= formatOnImportOn def
<*> o .:? "formattingProvider" .!= formattingProvider def
-- 2017-10-09 23:22:00.710515298 [ThreadId 11] - ---> {"jsonrpc":"2.0","method":"workspace/didChangeConfiguration","params":{"settings":{"languageServerHaskell":{"maxNumberOfProblems":100,"hlintOn":true}}}}
-- 2017-10-09 23:22:00.710667381 [ThreadId 15] - reactor:got didChangeConfiguration notification:
@ -60,7 +63,7 @@ instance FromJSON Config where
-- ,("maxNumberOfProblems",Number 100.0)]))])}}
instance ToJSON Config where
toJSON (Config h m d l c f) = object [ "languageServerHaskell" .= r ]
toJSON (Config h m d l c f fp) = object [ "languageServerHaskell" .= r ]
where
r = object [ "hlintOn" .= h
, "maxNumberOfProblems" .= m
@ -68,4 +71,5 @@ instance ToJSON Config where
, "liquidOn" .= l
, "completionSnippetsOn" .= c
, "formatOnImportOn" .= f
, "formattingProvider" .= fp
]

View File

@ -17,6 +17,8 @@ module Haskell.Ide.Engine.PluginUtils
, srcSpan2Loc
, unpackRealSrcSpan
, reverseMapFile
, extractRange
, fullRange
, fileInfo
, realSrcSpan2Range
, canonicalizeUri
@ -221,6 +223,27 @@ diffText' supports (f,fText) f2Text withDeletions =
-- ---------------------------------------------------------------------
extractRange :: Range -> T.Text -> T.Text
extractRange (Range (Position sl _) (Position el _)) s = newS
where focusLines = take (el-sl+1) $ drop sl $ T.lines s
newS = T.unlines focusLines
-- | Gets the range that covers the entire text
fullRange :: T.Text -> Range
fullRange s = Range startPos endPos
where startPos = Position 0 0
endPos = Position lastLine 0
{-
In order to replace everything including newline characters,
the end range should extend below the last line. From the specification:
"If you want to specify a range that contains a line including
the line ending character(s) then use an end position denoting
the start of the next line"
-}
lastLine = length $ T.lines s
-- ---------------------------------------------------------------------
-- | Returns the directory and file name
fileInfo :: T.Text -> (FilePath,FilePath)
fileInfo tfileName =

View File

@ -39,6 +39,8 @@ module Haskell.Ide.Engine.PluginsIdeMonads
, DiagnosticTrigger(..)
, HoverProvider
, SymbolProvider
, FormattingType(..)
, FormattingProvider
, IdePlugins(..)
, getDiagnosticProvidersConfig
-- * IDE monads
@ -66,11 +68,13 @@ module Haskell.Ide.Engine.PluginsIdeMonads
, Location(..)
, TextDocumentIdentifier(..)
, TextDocumentPositionParams(..)
, TextEdit(..)
, WorkspaceEdit(..)
, Diagnostic(..)
, DiagnosticSeverity(..)
, PublishDiagnosticsParams(..)
, List(..)
, FormattingOptions(..)
)
where
@ -114,6 +118,7 @@ import Language.Haskell.LSP.Types ( Command(..)
, DiagnosticSeverity(..)
, DocumentSymbol(..)
, List(..)
, FormattingOptions(..)
, Hover(..)
, Location(..)
, Position(..)
@ -121,6 +126,7 @@ import Language.Haskell.LSP.Types ( Command(..)
, Range(..)
, TextDocumentIdentifier(..)
, TextDocumentPositionParams(..)
, TextEdit(..)
, Uri(..)
, VersionedTextDocumentIdentifier(..)
, WorkspaceEdit(..)
@ -202,6 +208,10 @@ type HoverProvider = Uri -> Position -> IdeM (IdeResult [Hover])
type SymbolProvider = Uri -> IdeDeferM (IdeResult [DocumentSymbol])
data FormattingType = FormatDocument
| FormatRange Range
type FormattingProvider = Uri -> FormattingType -> FormattingOptions -> IdeGhcM (IdeResult [TextEdit])
data PluginDescriptor =
PluginDescriptor { pluginId :: PluginId
, pluginName :: T.Text
@ -211,6 +221,7 @@ data PluginDescriptor =
, pluginDiagnosticProvider :: Maybe DiagnosticProvider
, pluginHoverProvider :: Maybe HoverProvider
, pluginSymbolProvider :: Maybe SymbolProvider
, pluginFormattingProvider :: Maybe FormattingProvider
} deriving (Generic)
instance Show PluginCommand where

View File

@ -29,13 +29,14 @@ import qualified Language.Haskell.LSP.Types as J
-- ---------------------------------------------------------------------
data REnv = REnv
{ scheduler :: Scheduler.Scheduler R
, lspFuncs :: Core.LspFuncs Config
{ scheduler :: Scheduler.Scheduler R
, lspFuncs :: Core.LspFuncs Config
-- | The process ID of HIE. See 'HasPidCache'
, reactorPidCache :: Int
, diagnosticSources :: Map.Map DiagnosticTrigger [(PluginId,DiagnosticProviderFunc)]
, hoverProviders :: [HoverProvider]
, symbolProviders :: [SymbolProvider]
, reactorPidCache :: Int
, diagnosticSources :: Map.Map DiagnosticTrigger [(PluginId,DiagnosticProviderFunc)]
, hoverProviders :: [HoverProvider]
, symbolProviders :: [SymbolProvider]
, formattingProviders :: Map.Map PluginId FormattingProvider
-- TODO: Add code action providers here
}
@ -56,11 +57,12 @@ runReactor
-> Map.Map DiagnosticTrigger [(PluginId, DiagnosticProviderFunc)]
-> [HoverProvider]
-> [SymbolProvider]
-> Map.Map PluginId FormattingProvider
-> R a
-> IO a
runReactor lf sc dps hps sps f = do
runReactor lf sc dps hps sps fps f = do
pid <- getProcessID
runReaderT f (REnv sc lf pid dps hps sps)
runReaderT f (REnv sc lf pid dps hps sps fps)
-- ---------------------------------------------------------------------

View File

@ -47,6 +47,7 @@ applyRefactDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -44,6 +44,7 @@ baseDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -18,6 +18,7 @@ import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.PluginUtils
import Language.Haskell.Brittany
import qualified Language.Haskell.LSP.Types as J
import qualified Language.Haskell.LSP.Types.Lens as J
import System.FilePath (FilePath, takeDirectory)
import Data.Maybe (maybeToList)
@ -37,11 +38,15 @@ brittanyDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Just provider
}
where
cmd :: CommandFunc FormatParams [J.TextEdit]
cmd =
CmdSync $ \(FormatParams tabSize uri range) -> brittanyCmd tabSize uri range
provider :: FormattingProvider
provider uri FormatDocument opts = brittanyCmd (opts ^. J.tabSize) uri Nothing
provider uri (FormatRange r) opts = brittanyCmd (opts ^. J.tabSize) uri (Just r)
brittanyCmd :: Int -> Uri -> Maybe Range -> IdeGhcM (IdeResult [J.TextEdit])
brittanyCmd tabSize uri range =
@ -64,24 +69,8 @@ brittanyCmd tabSize uri range =
case res of
Left err -> return $ IdeResultFail (IdeError PluginError
(T.pack $ "brittanyCmd: " ++ unlines (map showErr err)) Null)
Right newText -> do
let startPos = Position 0 0
endPos = Position lastLine 0
{-
In order to replace everything including newline characters,
the end range should extend below the last line. From the specification:
"If you want to specify a range that contains a line including
the line ending character(s) then use an end position denoting
the start of the next line"
-}
lastLine = length $ T.lines text
textEdit = J.TextEdit (Range startPos endPos) newText
return $ IdeResultOk [textEdit]
extractRange :: Range -> Text -> Text
extractRange (Range (Position sl _) (Position el _)) s = newS
where focusLines = take (el-sl+1) $ drop sl $ T.lines s
newS = T.unlines focusLines
Right newText ->
return $ IdeResultOk [J.TextEdit (fullRange text) newText]
normalize :: Range -> Range
normalize (Range (Position sl _) (Position el _)) =

View File

@ -161,6 +161,7 @@ buildPluginDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
data OperationMode = StackMode | CabalMode

View File

@ -38,6 +38,7 @@ example2Descriptor plId = PluginDescriptor
= Just (DiagnosticProvider (S.singleton DiagnosticOnSave) (DiagnosticProviderSync diagnosticProvider))
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -0,0 +1,41 @@
{-# LANGUAGE OverloadedStrings #-}
module Haskell.Ide.Engine.Plugin.Floskell
( floskellDescriptor
)
where
import Data.Aeson ( Value(Null) )
import qualified Data.ByteString.Lazy as BS
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as T
import qualified GhcMod.Utils as GM
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.PluginUtils
import FloskellFloskell
import Control.Monad.IO.Class
floskellDescriptor :: PluginId -> PluginDescriptor
floskellDescriptor plId = PluginDescriptor
{ pluginId = plId
, pluginName = "Floskell"
, pluginDesc = "Floskell is a flexible Haskell source code pretty printer."
, pluginCommands = []
, pluginCodeActionProvider = Nothing
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Just provider
}
provider :: FormattingProvider
provider uri typ _opts = pluginGetFile "floskell: " uri $ \file -> do
contents <- GM.withMappedFile file (liftIO . T.readFile)
let (range, selectedContents) = case typ of
FormatDocument -> (fullRange contents, contents)
FormatRange r -> (r, extractRange r contents)
result = reformat defaultAppConfig (uriToFilePath uri) (T.encodeUtf8 selectedContents)
case result of
Left err -> return $ IdeResultFail (IdeError PluginError (T.pack err) Null)
Right new -> return $ IdeResultOk [TextEdit range (T.decodeUtf8 (BS.toStrict new))]

View File

@ -69,6 +69,7 @@ ghcmodDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Just hoverProvider
, pluginSymbolProvider = Just symbolProvider
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -72,6 +72,7 @@ hareDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -47,6 +47,7 @@ haddockDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Just hoverProvider
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}

View File

@ -37,6 +37,7 @@ hfaAlignDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -37,6 +37,7 @@ hoogleDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -41,6 +41,7 @@ hsimportDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
data ImportParams = ImportParams

View File

@ -48,6 +48,7 @@ liquidDescriptor plId = PluginDescriptor
(DiagnosticProviderAsync diagnosticProvider))
, pluginHoverProvider = Just hoverProvider
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -60,6 +60,7 @@ packageDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
data AddParams = AddParams

View File

@ -27,6 +27,7 @@ pragmasDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -123,7 +123,7 @@ run scheduler _origDir plugins captureFp = flip E.catches handlers $ do
let dp lf = do
diagIn <- atomically newTChan
let react = runReactor lf scheduler diagnosticProviders hps sps
let react = runReactor lf scheduler diagnosticProviders hps sps fps
reactorFunc = react $ reactor rin diagIn
let errorHandler :: Scheduler.ErrorHandler
@ -175,6 +175,9 @@ run scheduler _origDir plugins captureFp = flip E.catches handlers $ do
sps :: [SymbolProvider]
sps = mapMaybe pluginSymbolProvider $ Map.elems $ ipMap plugins
fps :: Map.Map PluginId FormattingProvider
fps = Map.mapMaybe pluginFormattingProvider $ ipMap plugins
flip E.finally finalProc $ do
CTRL.run (getConfigFromNotification, dp) (hieHandlers rin) (hieOptions commandIds) captureFp
where
@ -718,13 +721,27 @@ reactor inp diagIn = do
ReqDocumentFormatting req -> do
liftIO $ U.logs $ "reactor:got FormatRequest:" ++ show req
let params = req ^. J.params
doc = params ^. J.textDocument . J.uri
tabSize = params ^. J.options . J.tabSize
callback = reactorSend . RspDocumentFormatting . Core.makeResponseMessage req . J.List
let hreq = GReq tn (Just doc) Nothing (Just $ req ^. J.id) callback
$ Brittany.brittanyCmd tabSize doc Nothing
makeRequest hreq
providers <- asks formattingProviders
lf <- asks lspFuncs
mc <- liftIO $ Core.config lf
let providerName = formattingProvider (fromMaybe def mc)
providerType = Map.lookup providerName providers
case providerType of
Nothing -> do
reactorSend (RspDocumentFormatting (Core.makeResponseMessage req (J.List [])))
unless (providerName == "none") $ do
let msg = providerName <> " is not a recognised plugin for formatting. Check your config"
reactorSend $ NotShowMessage $ fmServerShowMessageNotification J.MtWarning msg
reactorSend $ NotLogMessage $ fmServerLogMessageNotification J.MtWarning msg
Just provider ->
-- LL: Is this overengineered? Do we need a pluginFormattingProvider
-- or should we just call plugins straight from here based on the providerType?
let params = req ^. J.params
doc = params ^. J.textDocument . J.uri
callback = reactorSend . RspDocumentFormatting . Core.makeResponseMessage req . J.List
hreq = GReq tn (Just doc) Nothing (Just $ req ^. J.id) callback
$ provider doc FormatDocument (params ^. J.options)
in makeRequest hreq
-- -------------------------------

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/cabal-helper
- ./submodules/floskell
# - brittany-0.11.0.0
- butcher-1.3.1.1
@ -23,6 +24,7 @@ extra-deps:
- hlint-2.0.11
- hsimport-0.8.6
- lsp-test-0.5.0.2
- monad-dijkstra-0.1.1.2
- pretty-show-1.8.2
- sorted-list-0.2.1.0
- syz-0.2.0.0

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/cabal-helper
- ./submodules/floskell
# - brittany-0.11.0.0
- butcher-1.3.1.1
@ -26,6 +27,7 @@ extra-deps:
- hoogle-5.0.17.5
- hsimport-0.8.8
- lsp-test-0.5.0.2
- monad-dijkstra-0.1.1.2
- pretty-show-1.8.2
- sorted-list-0.2.1.0
- syz-0.2.0.0

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/cabal-helper
- ./submodules/floskell
- base-compat-0.9.3
# - brittany-0.11.0.0

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/cabal-helper
- ./submodules/floskell
- base-compat-0.9.3
- cabal-plan-0.3.0.0
@ -23,6 +24,7 @@ extra-deps:
- hoogle-5.0.17.5
- hsimport-0.8.8
- lsp-test-0.5.0.2
- monad-dijkstra-0.1.1.2
- pretty-show-1.8.2
- syz-0.2.0.0
- temporary-1.2.1.1

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/cabal-helper
- ./submodules/floskell
# - brittany-0.11.0.0
- cabal-plan-0.4.0.0
@ -23,6 +24,7 @@ extra-deps:
- hoogle-5.0.17.5
- hsimport-0.8.8
- lsp-test-0.5.0.2
- monad-dijkstra-0.1.1.2
- optparse-simple-0.1.0
- pretty-show-1.9.5
- syz-0.2.0.0

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/cabal-helper
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/floskell
- apply-refact-0.6.0.0
- butcher-1.3.2.1
@ -25,6 +26,7 @@ extra-deps:
- hoogle-5.0.17.5
- hsimport-0.8.8
- lsp-test-0.5.0.2
- monad-dijkstra-0.1.1.2
- monad-memo-0.4.1
- monoid-subclasses-0.4.6.1
- multistate-0.8.0.1

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/cabal-helper
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/floskell
- butcher-1.3.2.1
- cabal-plan-0.4.0.0
@ -18,6 +19,7 @@ extra-deps:
- hlint-2.1.14
- hoogle-5.0.17.5
- hsimport-0.8.8
- monad-dijkstra-0.1.1.2
- monad-memo-0.4.1
- multistate-0.8.0.1
- syz-0.2.0.0

View File

@ -9,6 +9,7 @@ extra-deps:
- ./submodules/cabal-helper
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/floskell
- butcher-1.3.2.1
- cabal-plan-0.4.0.0
@ -18,6 +19,7 @@ extra-deps:
- hlint-2.1.14
- hoogle-5.0.17.5
- hsimport-0.8.8
- monad-dijkstra-0.1.1.2
- monad-memo-0.4.1
- multistate-0.8.0.1
- optparse-simple-0.1.0

View File

@ -1,4 +1,4 @@
resolver: nightly-2019-01-30 # GHC 8.6.3
resolver: nightly-2019-02-08 # GHC 8.6.3
packages:
- .
- hie-plugin-api
@ -9,6 +9,7 @@ extra-deps:
- ./submodules/cabal-helper
- ./submodules/ghc-mod
- ./submodules/ghc-mod/core
- ./submodules/floskell
- butcher-1.3.2.1
- cabal-plan-0.4.0.0
@ -18,6 +19,7 @@ extra-deps:
- hlint-2.1.14
- hsimport-0.8.8
- hoogle-5.0.17.5
- monad-dijkstra-0.1.1.2
- monad-memo-0.4.1
- multistate-0.8.0.1
- optparse-simple-0.1.0

1
submodules/floskell Submodule

@ -0,0 +1 @@
Subproject commit c78442a160b873659cc0a4b22a88c444e5f3691f

View File

@ -126,9 +126,7 @@ spec = describe "completions" $ do
_ <- applyEdit doc te
compls <- getCompletions doc (Position 0 24)
-- liftIO $ putStrLn $ "completions=" ++ show (map (^.label) compls)
let item = head $ filter ((== "Wno-redundant-constraints") . (^. label)) compls
liftIO $ putStrLn $ "item=" ++ show item
liftIO $ do
item ^. label `shouldBe` "Wno-redundant-constraints"
item ^. kind `shouldBe` Just CiKeyword

View File

@ -7,7 +7,6 @@ import qualified Data.HashMap.Strict as H
import Haskell.Ide.Engine.Plugin.ApplyRefact
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.PluginUtils
import Language.Haskell.LSP.Types
import System.Directory
import TestUtils

View File

@ -45,6 +45,7 @@ testDescriptor plId = PluginDescriptor
, pluginDiagnosticProvider = Nothing
, pluginHoverProvider = Nothing
, pluginSymbolProvider = Nothing
, pluginFormattingProvider = Nothing
}
-- ---------------------------------------------------------------------

View File

@ -102,4 +102,4 @@ instance Arbitrary Position where
return $ Position l c
instance Arbitrary Config where
arbitrary = Config <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
arbitrary = Config <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary