mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
add JSON Grammar datatype
This commit is contained in:
parent
0900bdbe74
commit
699f8c343b
@ -1,13 +1,13 @@
|
|||||||
-- | Semantic functionality for JSON programs.
|
-- | Semantic functionality for JSON programs.
|
||||||
module Language.JSON
|
module Language.JSON
|
||||||
( Term(..)
|
( Term(..)
|
||||||
, TreeSitter.JSON.tree_sitter_json
|
, Language.JSON.Grammar.tree_sitter_json
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import qualified Language.JSON.AST as JSON
|
import qualified Language.JSON.AST as JSON
|
||||||
import qualified Tags.Tagging.Precise as Tags
|
import qualified Tags.Tagging.Precise as Tags
|
||||||
import qualified TreeSitter.JSON (tree_sitter_json)
|
import qualified Language.JSON.Grammar (tree_sitter_json)
|
||||||
import qualified AST.Unmarshal as TS
|
import qualified AST.Unmarshal as TS
|
||||||
|
|
||||||
newtype Term a = Term { getTerm :: JSON.Document a }
|
newtype Term a = Term { getTerm :: JSON.Document a }
|
||||||
|
@ -15,6 +15,6 @@ module Language.JSON.AST
|
|||||||
|
|
||||||
import Prelude hiding (String)
|
import Prelude hiding (String)
|
||||||
import AST.GenerateSyntax
|
import AST.GenerateSyntax
|
||||||
import qualified TreeSitter.JSON as Grammar
|
import qualified Language.JSON.Grammar as Grammar
|
||||||
|
|
||||||
astDeclarationsForLanguage Grammar.tree_sitter_json "../../../vendor/tree-sitter-json/src/node-types.json"
|
astDeclarationsForLanguage Grammar.tree_sitter_json "../../../vendor/tree-sitter-json/src/node-types.json"
|
||||||
|
15
semantic-json/src/Language/JSON/Grammar.hs
Normal file
15
semantic-json/src/Language/JSON/Grammar.hs
Normal file
@ -0,0 +1,15 @@
|
|||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
module Language.JSON.Grammar
|
||||||
|
( tree_sitter_json
|
||||||
|
, Grammar(..)
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Language.Haskell.TH
|
||||||
|
import TreeSitter.JSON.Internal
|
||||||
|
import TreeSitter.Language
|
||||||
|
|
||||||
|
-- Regenerate template haskell code when these files change:
|
||||||
|
addDependentFileRelative "../../../vendor/tree-sitter-json/src/parser.c"
|
||||||
|
|
||||||
|
-- | Statically-known rules corresponding to symbols in the grammar.
|
||||||
|
mkSymbolDatatype (mkName "Grammar") tree_sitter_json
|
@ -10,7 +10,7 @@ import Parsing.TreeSitter
|
|||||||
import Source.Source
|
import Source.Source
|
||||||
import SpecHelpers
|
import SpecHelpers
|
||||||
import qualified System.Path as Path
|
import qualified System.Path as Path
|
||||||
import TreeSitter.JSON (Grammar, tree_sitter_json)
|
import Language.JSON.Grammar (Grammar, tree_sitter_json)
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
|
Loading…
Reference in New Issue
Block a user