Update hie-plugin-api for use with HaRe (#61)

* Fix -Wall

* Re-enable runIdeGhcMBare and move runWithContext into the PluginAPI

So it can be used in standalone plugins, like HaRe

* Move runWithContext and runIdeGhcMBare to tests and Hare

* Use HaRe updated to use the current hie-bios/hie-plugin-api

* Make hie-plugin-api compile with GHC 8.8.1
This commit is contained in:
Alan Zimmerman 2019-11-25 10:50:04 +00:00 committed by Matthew Pickering
parent e212df1ece
commit d3d8ac2cf9
8 changed files with 28 additions and 24 deletions

View File

@ -158,7 +158,9 @@ namesFromHsIbWc :: HsTypes.LHsSigWcType GhcRn -> [Name]
namesFromHsIbSig :: HsTypes.LHsSigType GhcRn -> [Name]
namesFromHsWC :: HsTypes.LHsWcType GhcRn -> [Name]
-- | Monomorphising type so uniplate is happier.
#if __GLASGOW_HASKELL__ >= 806
#if __GLASGOW_HASKELL__ >= 808
namesFromHsIbSig = HsTypes.hsib_ext
#elif __GLASGOW_HASKELL__ >= 806
namesFromHsIbSig = hsib_vars . HsTypes.hsib_ext
#else
namesFromHsIbSig = HsTypes.hsib_vars
@ -546,4 +548,4 @@ node_dependencies n =
in deps
#endif
verticesG = Digraph.verticesG
verticesG = Digraph.verticesG

View File

@ -106,6 +106,7 @@ runActionWithContext df (Just uri) def action = do
mcradle <- getCradle uri
loadCradle df mcradle def action
-- ---------------------------------------------------------------------
-- | Load the Cradle based on the given DynFlags and Cradle lookup Result.
-- Reuses a Cradle if possible and sets up a GHC session for a new Cradle

View File

@ -38,7 +38,7 @@ module Haskell.Ide.Engine.PluginApi
, HIE.IdeState(..)
, HIE.IdeGhcM
, HIE.runIdeGhcM
, runIdeGhcMBare
, HIE.runActionWithContext
, HIE.IdeM
, HIE.runIdeM
, HIE.IdeDeferM
@ -54,23 +54,30 @@ module Haskell.Ide.Engine.PluginApi
, HIE.Diagnostics
, HIE.AdditionalErrs
, LSP.filePathToUri
, LSP.uriToFilePath
, LSP.Uri
, HIE.ifCachedModule
, HIE.CachedInfo(..)
, HIE.IdeResult(..)
-- * used for tests in HaRe
, BiosLogLevel
, BiosOptions
, defaultOptions
, HIE.BIOSVerbosity(..)
, HIE.CradleOpts(..)
, emptyIdePlugins
, emptyIdeState
) where
import qualified GhcProject.Types as GP
import qualified Haskell.Ide.Engine.Ghc as HIE
import qualified Haskell.Ide.Engine.GhcModuleCache as HIE (CachedInfo(..),HasGhcModuleCache(..))
import qualified Haskell.Ide.Engine.ModuleCache as HIE (ifCachedModule)
import qualified Haskell.Ide.Engine.GhcModuleCache as HIE (CachedInfo(..),HasGhcModuleCache(..),emptyModuleCache)
import qualified Haskell.Ide.Engine.ModuleCache as HIE (ifCachedModule,runActionWithContext )
import qualified Haskell.Ide.Engine.PluginsIdeMonads as HIE
import qualified Language.Haskell.LSP.Types as LSP ( filePathToUri )
import qualified Language.Haskell.LSP.Types as LSP ( filePathToUri, uriToFilePath, Uri )
import qualified HIE.Bios.Types as HIE
defaultOptions :: HIE.CradleOpts
@ -78,5 +85,9 @@ defaultOptions = HIE.defaultCradleOpts
type BiosLogLevel = HIE.BIOSVerbosity
type BiosOptions = HIE.CradleOpts
runIdeGhcMBare :: a
runIdeGhcMBare = error "Not implemented"
emptyIdePlugins :: HIE.IdePlugins
emptyIdePlugins = HIE.IdePlugins mempty
emptyIdeState :: HIE.IdeState
emptyIdeState = HIE.IdeState HIE.emptyModuleCache mempty mempty Nothing

View File

@ -57,7 +57,7 @@ import Language.Haskell.LSP.VFS
import Language.Haskell.LSP.Types.Capabilities
import qualified Language.Haskell.LSP.Types as J
import Prelude hiding (log)
import SrcLoc
import SrcLoc (SrcSpan(..), RealSrcSpan(..))
import Exception
import System.Directory
import System.FilePath

View File

@ -51,7 +51,6 @@ module Haskell.Ide.Engine.PluginsIdeMonads
, IdeState(..)
, IdeGhcM
, runIdeGhcM
-- , runIdeGhcMBare
, IdeM
, runIdeM
, IdeDeferM
@ -359,18 +358,6 @@ runIdeGhcM plugins mlf stateVar f = do
env <- IdeEnv <$> pure mlf <*> getProcessID <*> pure plugins
flip runReaderT stateVar $ flip runReaderT env $ BIOS.withGhcT f
{-
-- | Run an IdeGhcM in an external context (e.g. HaRe), with no plugins or LSP functions
runIdeGhcMBare :: BiosOptions -> IdeGhcM a -> IO a
runIdeGhcMBare biosOptions f = do
let
plugins = IdePlugins Map.empty
mlf = Nothing
initialState = IdeState emptyModuleCache Map.empty Map.empty Nothing
stateVar <- newTVarIO initialState
runIdeGhcM biosOptions plugins mlf stateVar f
-}
-- | A computation that is deferred until the module is cached.
-- Note that the module may not typecheck, in which case 'UriCacheFailed' is passed
data Defer a = Defer FilePath (UriCacheResult -> a) deriving Functor

View File

@ -328,6 +328,7 @@ ghcDispatcher env@DispatcherEnv { docVersionTVar } errorHandler callbackHandler
let
runner :: a -> IdeGhcM a -> IdeGhcM (IdeResult a)
runner a act = case context of
Nothing -> runActionWithContext iniDynFlags Nothing a act
Just uri -> case uriToFilePath uri of

@ -1 +1 @@
Subproject commit 26d1048d30ac5d995af46b35c9988172ecfb1f3e
Subproject commit 33a6fe617acc672d0f19f96cb557ca82651ffa54

View File

@ -11,6 +11,7 @@ import Data.Aeson
import qualified Data.Map as M
import qualified Data.HashMap.Strict as H
import Haskell.Ide.Engine.Ghc
import Haskell.Ide.Engine.PluginApi
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.PluginUtils
import Haskell.Ide.Engine.Plugin.HaRe
@ -21,7 +22,6 @@ import Language.Haskell.LSP.Types ( Location(..)
import System.Directory
import System.FilePath
import TestUtils
import GhcMonad
import Test.Hspec
-- ---------------------------------------------------------------------
@ -58,6 +58,8 @@ runWithContext uri act = case uriToFilePath uri of
IdeResultFail err -> error $ "Could not run in context: " ++ show err
Nothing -> error $ "uri not valid: " ++ show uri
-- ---------------------------------------------------------------------
hareSpec :: Spec
hareSpec = do
describe "hare plugin commands(old plugin api)" $ do