Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from 8 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions app/MainHie.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ import System.IO
import Haskell.Ide.Engine.Plugin.ApplyRefact
import Haskell.Ide.Engine.Plugin.Brittany
import Haskell.Ide.Engine.Plugin.Example2
import Haskell.Ide.Engine.Plugin.Bios
-- import Haskell.Ide.Engine.Plugin.HaRe
import Haskell.Ide.Engine.Plugin.Haddock
import Haskell.Ide.Engine.Plugin.HfaAlign
Expand Down Expand Up @@ -56,7 +55,6 @@ plugins includeExamples = pluginDescToIdePlugins allPlugins
, packageDescriptor "package"
, pragmasDescriptor "pragmas"
, floskellDescriptor "floskell"
, biosDescriptor "bios"
, genericDescriptor "generic"
]
examplePlugins =
Expand Down
1 change: 0 additions & 1 deletion haskell-ide-engine.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ library
Haskell.Ide.Engine.Plugin.Brittany
Haskell.Ide.Engine.Plugin.Example2
Haskell.Ide.Engine.Plugin.Floskell
Haskell.Ide.Engine.Plugin.Bios
-- Haskell.Ide.Engine.Plugin.HaRe
Haskell.Ide.Engine.Plugin.Haddock
Haskell.Ide.Engine.Plugin.HfaAlign
Expand Down
61 changes: 30 additions & 31 deletions hie-plugin-api/Haskell/Ide/Engine/PluginsIdeMonads.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,12 +24,11 @@ module Haskell.Ide.Engine.PluginsIdeMonads
, allLspCmdIds
, mkLspCmdId
-- * Plugins
, PluginId
, CommandName
, PluginId(..)
, CommandId(..)
, PluginDescriptor(..)
, pluginDescToIdePlugins
, PluginCommand(..)
, CommandFunc(..)
, runPluginCommand
, DynamicJSON
, dynToJSON
Expand Down Expand Up @@ -114,6 +113,7 @@ import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid ( (<>) )
import qualified Data.Set as S
import Data.String
import qualified Data.Text as T
import Data.Typeable ( TypeRep
, Typeable
Expand Down Expand Up @@ -176,7 +176,7 @@ instance HasPidCache IO where
instance HasPidCache m => HasPidCache (IdeResultT m) where
getPidCache = lift getPidCache

mkLspCommand :: HasPidCache m => PluginId -> CommandName -> T.Text -> Maybe [Value] -> m Command
mkLspCommand :: HasPidCache m => PluginId -> CommandId -> T.Text -> Maybe [Value] -> m Command
mkLspCommand plid cn title args' = do
cmdId <- mkLspCmdId plid cn
let args = List <$> args'
Expand All @@ -185,12 +185,12 @@ mkLspCommand plid cn title args' = do
allLspCmdIds :: HasPidCache m => IdePlugins -> m [T.Text]
allLspCmdIds (IdePlugins m) = concat <$> mapM go (Map.toList (pluginCommands <$> m))
where
go (plid, cmds) = mapM (mkLspCmdId plid . commandName) cmds
go (plid, cmds) = mapM (mkLspCmdId plid . commandId) cmds

mkLspCmdId :: HasPidCache m => PluginId -> CommandName -> m T.Text
mkLspCmdId plid cn = do
mkLspCmdId :: HasPidCache m => PluginId -> CommandId -> m T.Text
mkLspCmdId (PluginId plid) (CommandId cid) = do
pid <- T.pack . show <$> getPidCache
return $ pid <> ":" <> plid <> ":" <> cn
return $ pid <> ":" <> plid <> ":" <> cid

-- ---------------------------------------------------------------------
-- Plugins
Expand Down Expand Up @@ -261,10 +261,13 @@ type FormattingProvider = T.Text -- ^ Text to format
-> FormattingOptions -- ^ Options for the formatter
-> IdeM (IdeResult [TextEdit]) -- ^ Result of the formatting or the unchanged text.

newtype PluginId = PluginId T.Text
deriving (Show, Read, Eq, Ord)
instance IsString PluginId where
fromString = PluginId . T.pack

data PluginDescriptor =
PluginDescriptor { pluginId :: PluginId
, pluginName :: T.Text
, pluginDesc :: T.Text
, pluginCommands :: [PluginCommand]
, pluginCodeActionProvider :: Maybe CodeActionProvider
, pluginDiagnosticProvider :: Maybe DiagnosticProvider
Expand All @@ -274,17 +277,16 @@ data PluginDescriptor =
} deriving (Generic)

instance Show PluginCommand where
show (PluginCommand name _ _) = "PluginCommand { name = " ++ T.unpack name ++ " }"

type PluginId = T.Text
type CommandName = T.Text
show (PluginCommand i _) = "PluginCommand { name = " ++ show i ++ " }"

newtype CommandFunc a b = CmdSync (a -> IdeGhcM (IdeResult b))
newtype CommandId = CommandId T.Text
deriving (Show, Read, Eq, Ord)
instance IsString CommandId where
fromString = CommandId . T.pack

data PluginCommand = forall a b. (FromJSON a, ToJSON b, Typeable b) =>
PluginCommand { commandName :: CommandName
, commandDesc :: T.Text
, commandFunc :: CommandFunc a b
PluginCommand { commandId :: CommandId
, commandFunc :: a -> IdeGhcM (IdeResult b)
}

pluginDescToIdePlugins :: [PluginDescriptor] -> IdePlugins
Expand All @@ -301,21 +303,23 @@ fromDynJSON = CD.fromDynamic
toDynJSON :: (Typeable a, ToJSON a) => a -> DynamicJSON
toDynJSON = CD.toDyn

-- | Runs a plugin command given a PluginId, CommandName and
-- | Runs a plugin command given a PluginId, CommandId and
-- arguments in the form of a JSON object.
runPluginCommand :: PluginId -> CommandName -> Value
runPluginCommand :: PluginId -> CommandId -> Value
-> IdeGhcM (IdeResult DynamicJSON)
runPluginCommand p com arg = do
let PluginId p' = p
CommandId com' = com
IdePlugins m <- getPlugins
case Map.lookup p m of
Nothing -> return $
IdeResultFail $ IdeError UnknownPlugin ("Plugin " <> p <> " doesn't exist") Null
Just PluginDescriptor { pluginCommands = xs } -> case List.find ((com ==) . commandName) xs of
IdeResultFail $ IdeError UnknownPlugin ("Plugin " <> p' <> " doesn't exist") Null
Just PluginDescriptor { pluginCommands = xs } -> case List.find ((com ==) . commandId) xs of
Nothing -> return $ IdeResultFail $
IdeError UnknownCommand ("Command " <> com <> " isn't defined for plugin " <> p <> ". Legal commands are: " <> T.pack(show $ map commandName xs)) Null
Just (PluginCommand _ _ (CmdSync f)) -> case fromJSON arg of
IdeError UnknownCommand ("Command " <> com' <> " isn't defined for plugin " <> p' <> ". Legal commands are: " <> T.pack(show $ map commandId xs)) Null
Just (PluginCommand _ f) -> case fromJSON arg of
Error err -> return $ IdeResultFail $
IdeError ParameterError ("error while parsing args for " <> com <> " in plugin " <> p <> ": " <> T.pack err) Null
IdeError ParameterError ("error while parsing args for " <> com' <> " in plugin " <> p' <> ": " <> T.pack err) Null
Success a -> do
res <- f a
return $ fmap toDynJSON res
Expand All @@ -325,11 +329,6 @@ newtype IdePlugins = IdePlugins
{ ipMap :: Map.Map PluginId PluginDescriptor
} deriving (Generic)

-- TODO:AZ this is a defective instance, do we actually need it?
-- Perhaps rather make a separate type explicitly for this purpose.
instance ToJSON IdePlugins where
toJSON (IdePlugins m) = toJSON $ fmap (\x -> (commandName x, commandDesc x)) <$> fmap pluginCommands m

-- | For the diagnostic providers in the config, return a map of
-- current enabled state, indexed by the plugin id.
getDiagnosticProvidersConfig :: Config -> Map.Map PluginId Bool
Expand Down Expand Up @@ -599,7 +598,7 @@ instance ExceptionMonad m => ExceptionMonad (ReaderT e m) where
q u (ReaderT b) = ReaderT (u . b)

instance MonadTrans GhcT where
lift m = liftGhcT m
lift = liftGhcT


instance MonadUnliftIO Ghc where
Expand Down
45 changes: 17 additions & 28 deletions src/Haskell/Ide/Engine/Plugin/ApplyRefact.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,9 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
-- | apply-refact applies refactorings specified by the refact package. It is
-- currently integrated into hlint to enable the automatic application of
-- suggestions.
module Haskell.Ide.Engine.Plugin.ApplyRefact where

import Control.Arrow
Expand Down Expand Up @@ -41,12 +44,9 @@ type HintTitle = T.Text
applyRefactDescriptor :: PluginId -> PluginDescriptor
applyRefactDescriptor plId = PluginDescriptor
{ pluginId = plId
, pluginName = "ApplyRefact"
, pluginDesc = "apply-refact applies refactorings specified by the refact package. It is currently integrated into hlint to enable the automatic application of suggestions."
, pluginCommands =
[ PluginCommand "applyOne" "Apply a single hint" applyOneCmd
, PluginCommand "applyAll" "Apply all hints to the file" applyAllCmd
, PluginCommand "lint" "Run hlint on the file to generate hints" lintCmd
[ PluginCommand "applyOne" applyOneCmd
, PluginCommand "applyAll" applyAllCmd
]
, pluginCodeActionProvider = Just codeActionProvider
, pluginDiagnosticProvider = Nothing
Expand All @@ -69,12 +69,9 @@ data OneHint = OneHint
, oneHintTitle :: HintTitle
} deriving (Eq, Show)

applyOneCmd :: CommandFunc ApplyOneParams WorkspaceEdit
applyOneCmd = CmdSync $ \(AOP uri pos title) -> do
applyOneCmd' uri (OneHint pos title)

applyOneCmd' :: Uri -> OneHint -> IdeGhcM (IdeResult WorkspaceEdit)
applyOneCmd' uri oneHint = pluginGetFile "applyOne: " uri $ \fp -> do
applyOneCmd :: ApplyOneParams -> IdeGhcM (IdeResult WorkspaceEdit)
applyOneCmd (AOP uri pos title) = pluginGetFile "applyOne: " uri $ \fp -> do
let oneHint = OneHint pos title
revMapp <- reverseFileMap
let defaultResult = do
debugm "applyOne: no access to the persisted file."
Expand All @@ -91,12 +88,8 @@ applyOneCmd' uri oneHint = pluginGetFile "applyOne: " uri $ \fp -> do

-- ---------------------------------------------------------------------

applyAllCmd :: CommandFunc Uri WorkspaceEdit
applyAllCmd = CmdSync $ \uri -> do
applyAllCmd' uri

applyAllCmd' :: Uri -> IdeGhcM (IdeResult WorkspaceEdit)
applyAllCmd' uri = pluginGetFile "applyAll: " uri $ \fp -> do
applyAllCmd :: Uri -> IdeGhcM (IdeResult WorkspaceEdit)
applyAllCmd uri = pluginGetFile "applyAll: " uri $ \fp -> do
let defaultResult = do
debugm "applyAll: no access to the persisted file."
return $ IdeResultOk mempty
Expand All @@ -111,26 +104,22 @@ applyAllCmd' uri = pluginGetFile "applyAll: " uri $ \fp -> do

-- ---------------------------------------------------------------------

lintCmd :: CommandFunc Uri PublishDiagnosticsParams
lintCmd = CmdSync $ \uri -> do
lintCmd' uri

-- AZ:TODO: Why is this in IdeGhcM?
lintCmd' :: Uri -> IdeGhcM (IdeResult PublishDiagnosticsParams)
lintCmd' uri = pluginGetFile "lintCmd: " uri $ \fp -> do
lint :: Uri -> IdeGhcM (IdeResult PublishDiagnosticsParams)
lint uri = pluginGetFile "lint: " uri $ \fp -> do
let
defaultResult = do
debugm "lintCmd: no access to the persisted file."
debugm "lint: no access to the persisted file."
return
$ IdeResultOk (PublishDiagnosticsParams (filePathToUri fp) $ List [])
withMappedFile fp defaultResult $ \file' -> do
eitherErrorResult <- liftIO
(try $ runExceptT $ runLintCmd file' [] :: IO
(try $ runExceptT $ runLint file' [] :: IO
(Either IOException (Either [Diagnostic] [Idea]))
)
case eitherErrorResult of
Left err -> return $ IdeResultFail
(IdeError PluginError (T.pack $ "lintCmd: " ++ show err) Null)
(IdeError PluginError (T.pack $ "lint: " ++ show err) Null)
Right res -> case res of
Left diags ->
return
Expand All @@ -143,8 +132,8 @@ lintCmd' uri = pluginGetFile "lintCmd: " uri $ \fp -> do
$ PublishDiagnosticsParams (filePathToUri fp)
$ List (map hintToDiagnostic $ stripIgnores fs)

runLintCmd :: FilePath -> [String] -> ExceptT [Diagnostic] IO [Idea]
runLintCmd fp args = do
runLint :: FilePath -> [String] -> ExceptT [Diagnostic] IO [Idea]
runLint fp args = do
(flags,classify,hint) <- liftIO $ argsSettings args
let myflags = flags { hseFlags = (hseFlags flags) { extensions = EnableExtension TypeApplications:extensions (hseFlags flags)}}
res <- bimapExceptT parseErrorToDiagnostic id $ ExceptT $ parseModuleEx myflags fp Nothing
Expand Down
32 changes: 0 additions & 32 deletions src/Haskell/Ide/Engine/Plugin/Bios.hs

This file was deleted.

3 changes: 1 addition & 2 deletions src/Haskell/Ide/Engine/Plugin/Brittany.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Brittany is a tool to format source code.
module Haskell.Ide.Engine.Plugin.Brittany where

import Control.Lens
Expand All @@ -20,8 +21,6 @@ import Data.Maybe (maybeToList)
brittanyDescriptor :: PluginId -> PluginDescriptor
brittanyDescriptor plId = PluginDescriptor
{ pluginId = plId
, pluginName = "Brittany"
, pluginDesc = "Brittany is a tool to format source code."
, pluginCommands = []
, pluginCodeActionProvider = Nothing
, pluginDiagnosticProvider = Nothing
Expand Down
21 changes: 10 additions & 11 deletions src/Haskell/Ide/Engine/Plugin/Example2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
-- | An example of writing an HIE plugin
module Haskell.Ide.Engine.Plugin.Example2 where

import Control.Lens
Expand All @@ -22,12 +23,10 @@ import qualified Language.Haskell.LSP.Types.Lens as J
example2Descriptor :: PluginId -> PluginDescriptor
example2Descriptor plId = PluginDescriptor
{ pluginId = plId
, pluginName = "Hello World"
, pluginDesc = "An example of writing an HIE plugin"
, pluginCommands =
[ PluginCommand "sayHello" "say hello" sayHelloCmd
, PluginCommand "sayHelloTo ""say hello to the passed in param" sayHelloToCmd
, PluginCommand "todo" "Add a TODO marker" todoCmd
[ PluginCommand "sayHello" sayHelloCmd
, PluginCommand "sayHelloTo" sayHelloToCmd
, PluginCommand "todo" todoCmd
]
, pluginCodeActionProvider = Just codeActionProvider
, pluginDiagnosticProvider
Expand All @@ -39,11 +38,11 @@ example2Descriptor plId = PluginDescriptor

-- ---------------------------------------------------------------------

sayHelloCmd :: CommandFunc () T.Text
sayHelloCmd = CmdSync $ \_ -> return (IdeResultOk sayHello)
sayHelloCmd :: () -> IdeGhcM (IdeResult T.Text)
sayHelloCmd () = return (IdeResultOk sayHello)

sayHelloToCmd :: CommandFunc T.Text T.Text
sayHelloToCmd = CmdSync $ \n -> do
sayHelloToCmd :: T.Text -> IdeGhcM (IdeResult T.Text)
sayHelloToCmd n = do
r <- liftIO $ sayHelloTo n
return $ IdeResultOk r

Expand Down Expand Up @@ -78,8 +77,8 @@ data TodoParams = TodoParams
}
deriving (Show, Eq, Generics.Generic, ToJSON, FromJSON)

todoCmd :: CommandFunc TodoParams J.WorkspaceEdit
todoCmd = CmdSync $ \(TodoParams uri r) -> return $ IdeResultOk $ makeTodo uri r
todoCmd :: TodoParams -> IdeGhcM (IdeResult J.WorkspaceEdit)
todoCmd (TodoParams uri r) = return $ IdeResultOk $ makeTodo uri r

makeTodo :: J.Uri -> J.Range -> J.WorkspaceEdit
makeTodo uri (J.Range (J.Position startLine _) _) = res
Expand Down
3 changes: 1 addition & 2 deletions src/Haskell/Ide/Engine/Plugin/Floskell.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}

-- | A flexible Haskell source code pretty printer.
module Haskell.Ide.Engine.Plugin.Floskell
( floskellDescriptor
)
Expand All @@ -17,8 +18,6 @@ import Haskell.Ide.Engine.PluginUtils
floskellDescriptor :: PluginId -> PluginDescriptor
floskellDescriptor plId = PluginDescriptor
{ pluginId = plId
, pluginName = "Floskell"
, pluginDesc = "A flexible Haskell source code pretty printer."
, pluginCommands = []
, pluginCodeActionProvider = Nothing
, pluginDiagnosticProvider = Nothing
Expand Down
Loading