mirror of
https://github.com/github/semantic.git
synced 2024-12-22 22:31:36 +03:00
Merge pull request #1077 from github/ruby-production-type
Templated grammar types
This commit is contained in:
commit
831c55d025
@ -1,6 +1,8 @@
|
||||
module Text.Parser.TreeSitter.Ruby where
|
||||
module Text.Parser.TreeSitter.Ruby
|
||||
( tree_sitter_ruby
|
||||
) where
|
||||
|
||||
import Text.Parser.TreeSitter
|
||||
import Foreign.Ptr
|
||||
import Text.Parser.TreeSitter
|
||||
|
||||
foreign import ccall unsafe "vendor/tree-sitter-ruby/src/parser.c tree_sitter_ruby" tree_sitter_ruby :: Ptr Language
|
||||
|
@ -44,11 +44,13 @@ library
|
||||
, Language
|
||||
, Language.C
|
||||
, Language.JavaScript
|
||||
, Language.TypeScript
|
||||
, Language.Markdown
|
||||
, Language.Go
|
||||
, Language.Go.Syntax
|
||||
, Language.Ruby
|
||||
, Language.Ruby.Syntax
|
||||
, Language.TypeScript
|
||||
, Language.TypeScript.Syntax
|
||||
, Parser
|
||||
, Patch
|
||||
, Paths_semantic_diff
|
||||
@ -108,6 +110,7 @@ library
|
||||
, regex-compat
|
||||
, semigroups
|
||||
, split
|
||||
, template-haskell
|
||||
, text >= 1.2.1.3
|
||||
, text-icu
|
||||
, these
|
||||
|
9
src/Language/Go/Syntax.hs
Normal file
9
src/Language/Go/Syntax.hs
Normal file
@ -0,0 +1,9 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Language.Go.Syntax where
|
||||
|
||||
import Language.Haskell.TH
|
||||
import Text.Parser.TreeSitter.Go
|
||||
import Text.Parser.TreeSitter.Language
|
||||
|
||||
-- | Statically-known rules corresponding to symbols in the grammar.
|
||||
mkSymbolDatatype (mkName "Grammar") tree_sitter_go
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DataKinds, TemplateHaskell #-}
|
||||
module Language.Ruby.Syntax where
|
||||
|
||||
import Control.Monad.Free.Freer
|
||||
@ -9,7 +9,10 @@ import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import Language.Haskell.TH
|
||||
import Prologue
|
||||
import Text.Parser.TreeSitter.Language
|
||||
import Text.Parser.TreeSitter.Ruby
|
||||
|
||||
-- | The type of Ruby syntax.
|
||||
type Syntax = Union
|
||||
@ -29,8 +32,8 @@ type Program = Freer
|
||||
|
||||
|
||||
-- | Statically-known rules corresponding to symbols in the grammar.
|
||||
data Grammar = Program | Uninterpreted | BeginBlock | EndBlock | Undef | Alias | Comment | True' | False' | Return | Yield | Break | Next | Redo | Retry | IfModifier | UnlessModifier | WhileModifier | UntilModifier | RescueModifier | While | Until | For | Do | Case | When | Pattern | If | Unless | Elsif | Else | Begin | Ensure | Rescue | Exceptions | ExceptionVariable | ElementReference | ScopeResolution | Call | MethodCall | ArgumentList | ArgumentListWithParens | SplatArgument | HashSplatArgument | BlockArgument | Class | Constant | Method | Identifier
|
||||
deriving (Enum, Eq, Ord, Show)
|
||||
mkSymbolDatatype (mkName "Grammar") tree_sitter_ruby
|
||||
|
||||
|
||||
-- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax.
|
||||
assignment :: Assignment Grammar (Program Syntax (Maybe a))
|
||||
|
9
src/Language/TypeScript/Syntax.hs
Normal file
9
src/Language/TypeScript/Syntax.hs
Normal file
@ -0,0 +1,9 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
module Language.TypeScript.Syntax where
|
||||
|
||||
import Language.Haskell.TH
|
||||
import Text.Parser.TreeSitter.Language
|
||||
import Text.Parser.TreeSitter.TypeScript
|
||||
|
||||
-- | Statically-known rules corresponding to symbols in the grammar.
|
||||
mkSymbolDatatype (mkName "Grammar") tree_sitter_typescript
|
2
vendor/haskell-tree-sitter
vendored
2
vendor/haskell-tree-sitter
vendored
@ -1 +1 @@
|
||||
Subproject commit e76073e4c6ccb75af73f86ac9fe5fc5496e4d44f
|
||||
Subproject commit 3a5fe620364de5688857bc5f7f10f59ae7207a04
|
Loading…
Reference in New Issue
Block a user