module HsInspect.LSP.Impl where
import Control.Monad.Extra (fromMaybeM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Except (ExceptT(..))
import Control.Monad.Trans.Except (throwE)
import Data.Cache (Cache)
import qualified Data.Cache as C
import qualified Data.List as L
import Data.Maybe (mapMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import qualified FastString as GHC
import qualified GHC as GHC
import GHC.Paths (libdir)
import HsInspect.LSP.Context
import HsInspect.LSP.HsInspect
import qualified Lexer as GHC
import qualified SrcLoc as GHC
import qualified StringBuffer as GHC
data Caches = Caches
(Cache FilePath Context)
(Cache FilePath [Import])
cachedContext :: Caches -> BuildTool -> FilePath -> ExceptT String IO Context
cachedContext (Caches cache _) tool file = do
let discover = mkDiscoverContext tool
key <- discoverPackageDir discover file
let work = do
ctx <- findContext discover file
liftIO $ C.insert cache key ctx
pure ctx
fromMaybeM work . liftIO $ C.lookup cache key
cachedImports :: Caches -> Context -> FilePath -> ExceptT String IO [Import]
cachedImports (Caches _ cache) ctx file =
C.fetchWithCache cache file $ imports mkHsInspect ctx
signatureHelpProvider :: Caches -> BuildTool -> FilePath -> (Int, Int) -> ExceptT String IO [Text]
signatureHelpProvider caches tool file position = do
ctx <- cachedContext caches tool file
symbols <- cachedImports caches ctx file
sym <- symbolAtPoint file position
let
matcher imp =
if _local imp == Just sym || _qual imp == Just sym || _full imp == sym
then Just $ _full imp
else Nothing
pure $ mapMaybe matcher symbols
symbolAtPoint :: FilePath -> (Int, Int) -> ExceptT String IO Text
symbolAtPoint file (line, col) = do
buf' <- liftIO $ GHC.hGetStringBuffer file
buf <- maybe (throwE "line doesn't exist") pure $ GHC.atLine 1 buf'
let file' = GHC.mkFastString file
startLoc = GHC.mkRealSrcLoc file' 1 1
point = GHC.realSrcLocSpan $ GHC.mkRealSrcLoc file' line (col + 1)
dflags <- liftIO . GHC.runGhc (Just libdir) $ GHC.getSessionDynFlags
case GHC.lexTokenStream buf startLoc dflags of
GHC.POk _ ts ->
let containsPoint :: GHC.SrcSpan -> Bool
containsPoint (GHC.UnhelpfulSpan _) = False
containsPoint (GHC.RealSrcSpan s) = GHC.containsSpan s point
in maybe (throwE "could not find a token") (pure . T.pack . snd) .
L.find (containsPoint . GHC.getLoc . fst) $
GHC.addSourceToTokens startLoc buf ts
_ -> throwE "lexer error"