1
1
mirror of https://github.com/github/semantic.git synced 2024-12-22 14:21:31 +03:00
semantic/src/TreeSitter.hs

63 lines
2.7 KiB
Haskell
Raw Normal View History

module TreeSitter where
2016-02-09 22:34:23 +03:00
import Category
2016-02-11 01:30:14 +03:00
import Language
import Parser
2016-02-11 01:30:14 +03:00
import Range
2015-12-24 08:20:47 +03:00
import Source
2015-12-16 23:49:46 +03:00
import qualified Data.Set as Set
import Foreign
import Foreign.C.String
import Text.Parser.TreeSitter hiding (Language(..))
import qualified Text.Parser.TreeSitter as TS
2016-02-11 02:07:27 +03:00
-- | Returns a TreeSitter parser for the given language and TreeSitter grammar.
treeSitterParser :: Language -> Ptr TS.Language -> Parser
2016-02-11 02:07:27 +03:00
treeSitterParser language grammar contents = do
document <- ts_document_make
ts_document_set_language document grammar
withCString (toList contents) (\source -> do
ts_document_set_input_string document source
ts_document_parse document
term <- documentToTerm (termConstructor $ categoriesForLanguage language) document contents
ts_document_free document
return term)
2016-02-11 01:59:48 +03:00
-- Given a language and a node name, return the correct categories.
categoriesForLanguage :: Language -> String -> Set.Set Category
categoriesForLanguage language name = case (language, name) of
(JavaScript, "object") -> Set.singleton DictionaryLiteral
2016-02-17 18:59:41 +03:00
(JavaScript, "rel_op") -> Set.singleton BinaryOperator -- relational operator, e.g. >, <, <=, >=, ==, !=
(Ruby, "hash") -> Set.singleton DictionaryLiteral
2016-02-11 01:59:48 +03:00
_ -> defaultCategoryForNodeName name
-- | Given a node name from TreeSitter, return the correct categories.
2016-02-11 01:57:01 +03:00
defaultCategoryForNodeName :: String -> Set.Set Category
defaultCategoryForNodeName name = case name of
"function_call" -> Set.singleton FunctionCall
2016-02-17 18:59:50 +03:00
"pair" -> Set.singleton Pair
"string" -> Set.singleton StringLiteral
"integer" -> Set.singleton IntegerLiteral
"symbol" -> Set.singleton SymbolLiteral
2016-03-03 07:03:47 +03:00
"array" -> Set.singleton ArrayLiteral
_ -> Set.singleton (Other name)
2016-02-09 22:34:23 +03:00
2016-02-03 21:24:17 +03:00
-- | Given a constructor and a tree sitter document, return a parser.
documentToTerm :: Constructor -> Ptr Document -> Parser
2015-12-23 18:34:40 +03:00
documentToTerm constructor document contents = alloca $ \ root -> do
ts_document_root_node_p document root
toTerm root
where toTerm node = do
name <- ts_node_p_name node document
2015-12-31 01:52:51 +03:00
name <- peekCString name
count <- ts_node_p_named_child_count node
2015-12-23 18:47:15 +03:00
children <- mapM (alloca . getChild node) $ take (fromIntegral count) [0..]
2015-12-24 01:54:28 +03:00
-- Note: The strict application here is semantically important. Without it, we may not evaluate the range until after weve exited the scope that `node` was allocated within, meaning `alloca` will free it & other stack data may overwrite it.
2015-12-24 01:39:13 +03:00
range <- return $! Range { start = fromIntegral $ ts_node_p_start_char node, end = fromIntegral $ ts_node_p_end_char node }
return $! constructor contents range name children
2015-12-23 18:47:15 +03:00
getChild node n out = do
_ <- ts_node_p_named_child node n out
2015-12-23 18:47:15 +03:00
toTerm out