mirror of
https://github.com/github/semantic.git
synced 2024-12-26 08:25:19 +03:00
Merge pull request #1124 from github/backport-repl-workflow-factoring
Backport “REPL workflow factoring”
This commit is contained in:
commit
1e59f65d27
@ -1,7 +1,6 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
module TreeSitter
|
module TreeSitter
|
||||||
( treeSitterParser
|
( treeSitterParser
|
||||||
, parseRubyToAST
|
|
||||||
, parseRubyToTerm
|
, parseRubyToTerm
|
||||||
, defaultTermAssignment
|
, defaultTermAssignment
|
||||||
) where
|
) where
|
||||||
@ -46,11 +45,11 @@ treeSitterParser language grammar blob = do
|
|||||||
pure term
|
pure term
|
||||||
|
|
||||||
|
|
||||||
-- | Parse Ruby to AST. Intended for use in ghci, e.g.:
|
-- | Parse Ruby to a list of Terms, printing any assignment errors to stdout. Intended for use in ghci, e.g.:
|
||||||
--
|
--
|
||||||
-- > Command.Files.readFile "/Users/rob/Desktop/test.rb" >>= parseRubyToAST . source
|
-- > Command.Files.readFile "/Users/rob/Desktop/test.rb" >>= parseRubyToTerm . source
|
||||||
parseRubyToAST :: Source -> IO (A.AST Ruby.Grammar)
|
parseRubyToTerm :: Source -> IO (Maybe [Term Ruby.Syntax A.Location])
|
||||||
parseRubyToAST source = do
|
parseRubyToTerm source = do
|
||||||
document <- ts_document_new
|
document <- ts_document_new
|
||||||
ts_document_set_language document Ruby.tree_sitter_ruby
|
ts_document_set_language document Ruby.tree_sitter_ruby
|
||||||
root <- withCStringLen (toText source) $ \ (source, len) -> do
|
root <- withCStringLen (toText source) $ \ (source, len) -> do
|
||||||
@ -63,31 +62,25 @@ parseRubyToAST source = do
|
|||||||
ast <- anaM toAST root
|
ast <- anaM toAST root
|
||||||
|
|
||||||
ts_document_free document
|
ts_document_free document
|
||||||
pure ast
|
|
||||||
where toAST :: Node -> IO (A.RoseF (A.Node Ruby.Grammar) Node)
|
|
||||||
toAST node@Node{..} = do
|
|
||||||
let count = fromIntegral nodeChildCount
|
|
||||||
children <- allocaArray count $ \ childNodesPtr -> do
|
|
||||||
_ <- with nodeTSNode (\ nodePtr -> ts_node_copy_child_nodes nullPtr nodePtr childNodesPtr (fromIntegral count))
|
|
||||||
peekArray count childNodesPtr
|
|
||||||
pure $ A.RoseF (toEnum (fromIntegral nodeSymbol) :. nodeRange node :. nodeSpan node :. Nil) children
|
|
||||||
|
|
||||||
anaM :: (Corecursive t, Monad m, Traversable (Base t)) => (a -> m (Base t a)) -> a -> m t
|
|
||||||
anaM g = a where a = pure . embed <=< traverse a <=< g
|
|
||||||
|
|
||||||
|
|
||||||
-- | Parse Ruby to a list of Terms, printing any assignment errors to stdout. Intended for use in ghci, e.g.:
|
|
||||||
--
|
|
||||||
-- > Command.Files.readFile "/Users/rob/Desktop/test.rb" >>= parseRubyToTerm . source
|
|
||||||
parseRubyToTerm :: Source -> IO (Maybe [Term Ruby.Syntax A.Location])
|
|
||||||
parseRubyToTerm source = do
|
|
||||||
ast <- parseRubyToAST source
|
|
||||||
let A.Result errors value = A.assign Ruby.assignment source ast
|
let A.Result errors value = A.assign Ruby.assignment source ast
|
||||||
case value of
|
case value of
|
||||||
Just a -> pure (Just a)
|
Just a -> pure (Just a)
|
||||||
_ -> traverse_ (putStrLn . ($ "") . A.showError source) errors >> pure Nothing
|
_ -> traverse_ (putStrLn . ($ "") . A.showError source) errors >> pure Nothing
|
||||||
|
|
||||||
|
|
||||||
|
toAST :: Enum grammar => Node -> IO (A.RoseF (A.Node grammar) Node)
|
||||||
|
toAST node@Node{..} = do
|
||||||
|
let count = fromIntegral nodeChildCount
|
||||||
|
children <- allocaArray count $ \ childNodesPtr -> do
|
||||||
|
_ <- with nodeTSNode (\ nodePtr -> ts_node_copy_child_nodes nullPtr nodePtr childNodesPtr (fromIntegral count))
|
||||||
|
peekArray count childNodesPtr
|
||||||
|
pure $ A.RoseF (toEnum (fromIntegral nodeSymbol) :. nodeRange node :. nodeSpan node :. Nil) children
|
||||||
|
|
||||||
|
anaM :: (Corecursive t, Monad m, Traversable (Base t)) => (a -> m (Base t a)) -> a -> m t
|
||||||
|
anaM g = a where a = pure . embed <=< traverse a <=< g
|
||||||
|
|
||||||
|
|
||||||
-- | Return a parser for a tree sitter language & document.
|
-- | Return a parser for a tree sitter language & document.
|
||||||
documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record DefaultFields)
|
documentToTerm :: Language -> Ptr Document -> Parser (Syntax.Syntax Text) (Record DefaultFields)
|
||||||
documentToTerm language document SourceBlob{..} = do
|
documentToTerm language document SourceBlob{..} = do
|
||||||
|
Loading…
Reference in New Issue
Block a user