Load from VFS
This commit is contained in:
parent
bf6cc6ca16
commit
29bc1721d1
@ -18,12 +18,13 @@ import Language.Haskell.LSP.Messages as Msg
|
|||||||
import qualified Language.Haskell.LSP.Types as J
|
import qualified Language.Haskell.LSP.Types as J
|
||||||
import qualified Language.Haskell.LSP.Types.Lens as J
|
import qualified Language.Haskell.LSP.Types.Lens as J
|
||||||
import qualified Language.Haskell.LSP.Utility as U
|
import qualified Language.Haskell.LSP.Utility as U
|
||||||
-- import Language.Haskell.LSP.VFS
|
import Language.Haskell.LSP.VFS
|
||||||
|
|
||||||
import System.Exit
|
import System.Exit
|
||||||
import qualified System.Log as L
|
import qualified System.Log as L
|
||||||
|
|
||||||
import Parser
|
import Parser
|
||||||
|
import ParseTree
|
||||||
import Range
|
import Range
|
||||||
import Product
|
import Product
|
||||||
import AST hiding (def)
|
import AST hiding (def)
|
||||||
@ -168,7 +169,7 @@ eventLoop funs chan = do
|
|||||||
ReqFindReferences req -> do
|
ReqFindReferences req -> do
|
||||||
let uri = req^.J.params.J.textDocument.J.uri
|
let uri = req^.J.params.J.textDocument.J.uri
|
||||||
let pos = posToRange $ req^.J.params.J.position
|
let pos = posToRange $ req^.J.params.J.position
|
||||||
tree <- loadByURI uri
|
tree <- loadFromVFS funs uri
|
||||||
case Find.referencesOf pos tree of
|
case Find.referencesOf pos tree of
|
||||||
Just refs -> do
|
Just refs -> do
|
||||||
let locations = J.Location uri . rangeToLoc <$> refs
|
let locations = J.Location uri . rangeToLoc <$> refs
|
||||||
@ -194,11 +195,22 @@ rangeToLoc (Range (a, b, _) (c, d, _) _) =
|
|||||||
(J.Position (a - 1) (b - 1))
|
(J.Position (a - 1) (b - 1))
|
||||||
(J.Position (c - 1) (d - 1))
|
(J.Position (c - 1) (d - 1))
|
||||||
|
|
||||||
|
loadFromVFS
|
||||||
|
:: Core.LspFuncs ()
|
||||||
|
-> J.Uri
|
||||||
|
-> IO (Pascal (Product [[ScopedDecl], Range, [Text]]))
|
||||||
|
loadFromVFS funs uri = do
|
||||||
|
Just vf <- Core.getVirtualFileFunc funs $ J.toNormalizedUri uri
|
||||||
|
let txt = virtualFileText vf
|
||||||
|
let Just fin = J.uriToFilePath uri
|
||||||
|
(tree, _) <- runParser contract (Text fin txt)
|
||||||
|
return $ addLocalScopes tree
|
||||||
|
|
||||||
loadByURI :: J.Uri -> IO (Pascal (Product [[ScopedDecl], Range, [Text]]))
|
loadByURI :: J.Uri -> IO (Pascal (Product [[ScopedDecl], Range, [Text]]))
|
||||||
loadByURI uri = do
|
loadByURI uri = do
|
||||||
case J.uriToFilePath uri of
|
case J.uriToFilePath uri of
|
||||||
Just fin -> do
|
Just fin -> do
|
||||||
(tree, _) <- runParser contract fin
|
(tree, _) <- runParser contract (Path fin)
|
||||||
return $ addLocalScopes tree
|
return $ addLocalScopes tree
|
||||||
|
|
||||||
collectErrors
|
collectErrors
|
||||||
@ -210,7 +222,7 @@ collectErrors
|
|||||||
collectErrors funs uri path version = do
|
collectErrors funs uri path version = do
|
||||||
case path of
|
case path of
|
||||||
Just fin -> do
|
Just fin -> do
|
||||||
(tree, errs) <- runParser contract fin
|
(tree, errs) <- runParser contract (Path fin)
|
||||||
Core.publishDiagnosticsFunc funs 100 uri version
|
Core.publishDiagnosticsFunc funs 100 uri version
|
||||||
$ partitionBySource
|
$ partitionBySource
|
||||||
$ map errorToDiag (errs <> errors tree)
|
$ map errorToDiag (errs <> errors tree)
|
||||||
|
@ -11,6 +11,7 @@ module ParseTree
|
|||||||
( -- * Tree/Forest
|
( -- * Tree/Forest
|
||||||
ParseTree(..)
|
ParseTree(..)
|
||||||
, ParseForest(..)
|
, ParseForest(..)
|
||||||
|
, Source(..)
|
||||||
|
|
||||||
-- * Invoke the TreeSitter and get the tree it outputs
|
-- * Invoke the TreeSitter and get the tree it outputs
|
||||||
, toParseTree
|
, toParseTree
|
||||||
@ -21,6 +22,7 @@ import Data.ByteString (ByteString)
|
|||||||
import Data.IORef
|
import Data.IORef
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
|
import qualified Data.Text.Encoding as Text
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Data.Traversable (for)
|
import Data.Traversable (for)
|
||||||
|
|
||||||
@ -49,6 +51,17 @@ import Pretty
|
|||||||
|
|
||||||
foreign import ccall unsafe tree_sitter_PascaLigo :: Ptr Language
|
foreign import ccall unsafe tree_sitter_PascaLigo :: Ptr Language
|
||||||
|
|
||||||
|
data Source
|
||||||
|
= Path { srcPath :: FilePath }
|
||||||
|
| Text { srcPath :: FilePath, srcText :: Text }
|
||||||
|
| ByteString { srcPath :: FilePath, srcBS :: ByteString }
|
||||||
|
|
||||||
|
srcToBytestring :: Source -> IO ByteString
|
||||||
|
srcToBytestring = \case
|
||||||
|
Path p -> BS.readFile p
|
||||||
|
Text _ t -> return $ Text.encodeUtf8 t
|
||||||
|
ByteString _ s -> return s
|
||||||
|
|
||||||
-- | The tree tree-sitter produces.
|
-- | The tree tree-sitter produces.
|
||||||
data ParseTree = ParseTree
|
data ParseTree = ParseTree
|
||||||
{ ptID :: Int -- ^ Unique number, for fast comparison.
|
{ ptID :: Int -- ^ Unique number, for fast comparison.
|
||||||
@ -85,12 +98,12 @@ instance Pretty ParseForest where
|
|||||||
else hang (text (Text.unpack field) <> ": ") 2 (pp tree)
|
else hang (text (Text.unpack field) <> ": ") 2 (pp tree)
|
||||||
|
|
||||||
-- | Feed file contents into PascaLIGO grammar recogniser.
|
-- | Feed file contents into PascaLIGO grammar recogniser.
|
||||||
toParseTree :: FilePath -> IO ParseForest
|
toParseTree :: Source -> IO ParseForest
|
||||||
toParseTree fin = do
|
toParseTree fin = do
|
||||||
parser <- ts_parser_new
|
parser <- ts_parser_new
|
||||||
True <- ts_parser_set_language parser tree_sitter_PascaLigo
|
True <- ts_parser_set_language parser tree_sitter_PascaLigo
|
||||||
|
|
||||||
src <- BS.readFile fin
|
src <- srcToBytestring fin
|
||||||
|
|
||||||
idCounter <- newIORef 0
|
idCounter <- newIORef 0
|
||||||
|
|
||||||
@ -146,7 +159,7 @@ toParseTree fin = do
|
|||||||
, i $ pointColumn finish2D + 1
|
, i $ pointColumn finish2D + 1
|
||||||
, i $ nodeEndByte node
|
, i $ nodeEndByte node
|
||||||
)
|
)
|
||||||
, rFile = takeFileName fin
|
, rFile = takeFileName $ srcPath fin
|
||||||
}
|
}
|
||||||
|
|
||||||
return $ ParseTree
|
return $ ParseTree
|
||||||
|
@ -103,12 +103,12 @@ type ASTInfo = Product [Range, [Text]]
|
|||||||
|
|
||||||
runParser
|
runParser
|
||||||
:: Parser a
|
:: Parser a
|
||||||
-> FilePath
|
-> Source
|
||||||
-> IO (a, [Error ASTInfo])
|
-> IO (a, [Error ASTInfo])
|
||||||
runParser parser fin = do
|
runParser parser fin = do
|
||||||
pforest <- toParseTree fin
|
pforest <- toParseTree fin
|
||||||
|
|
||||||
let dir = takeDirectory fin
|
let dir = takeDirectory $ srcPath fin
|
||||||
|
|
||||||
runWriterT parser `evalStateT`
|
runWriterT parser `evalStateT`
|
||||||
Cons pforest
|
Cons pforest
|
||||||
@ -128,7 +128,7 @@ restart p fin = do
|
|||||||
fallback "recusive imports"
|
fallback "recusive imports"
|
||||||
else do
|
else do
|
||||||
(a, errs) <- liftIO do
|
(a, errs) <- liftIO do
|
||||||
flip runParser full do
|
flip runParser (Path full) do
|
||||||
put' (Set.insert full set)
|
put' (Set.insert full set)
|
||||||
p
|
p
|
||||||
tell errs
|
tell errs
|
||||||
@ -319,7 +319,7 @@ some p = some'
|
|||||||
|
|
||||||
-- | Run parser on given file and pretty-print stuff.
|
-- | Run parser on given file and pretty-print stuff.
|
||||||
--
|
--
|
||||||
debugParser :: Show a => Parser a -> FilePath -> IO ()
|
debugParser :: Show a => Parser a -> Source -> IO ()
|
||||||
debugParser parser fin = do
|
debugParser parser fin = do
|
||||||
(res, errs) <- runParser parser fin
|
(res, errs) <- runParser parser fin
|
||||||
putStrLn "Result:"
|
putStrLn "Result:"
|
||||||
|
Loading…
Reference in New Issue
Block a user