1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 18:06:14 +03:00

🔥 the AST type synonym.

This commit is contained in:
Rob Rix 2017-06-07 15:19:32 -04:00
parent bc4284c8a6
commit 549d85a84d
3 changed files with 7 additions and 12 deletions

View File

@ -66,7 +66,6 @@ module Data.Syntax.Assignment
, symbol
, source
, children
, AST
, Result(..)
, Error(..)
, ErrorCause(..)
@ -135,10 +134,6 @@ children forEach = withFrozenCallStack $ Children forEach `Then` return
-- | A location specified as possibly-empty intervals of bytes and line/column positions.
type Location = '[Info.Range, Info.SourceSpan]
-- | An abstract syntax tree in some 'grammar', with symbols and location information annotating each node.
type AST grammar = Cofree [] (Record (Maybe grammar ': Location))
-- | The result of assignment, possibly containing an error.
data Result grammar a = Result { resultError :: Maybe (Error grammar), resultValue :: Maybe a }
deriving (Eq, Foldable, Functor, Traversable)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds, GADTs, ScopedTypeVariables, TypeOperators #-}
module Parser where
import Data.Functor.Union
@ -30,10 +30,10 @@ import TreeSitter
-- | A parser from 'Source' onto some term type.
data Parser term where
-- | A parser producing 'AST' using a 'TS.Language'.
ASTParser :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Parser (AST grammar)
ASTParser :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Parser (Cofree [] (Record (Maybe grammar ': Location)))
-- | A parser producing an à la carte term given an 'AST'-producing parser and an 'Assignment' onto 'Term's in some syntax type. Assignment errors will result in a top-level 'Syntax.Error' node.
AssignmentParser :: (Bounded grammar, Enum grammar, Eq grammar, Show grammar, Symbol grammar, InUnion fs (Syntax.Error (Error grammar)), Traversable (Union fs))
=> Parser (AST grammar) -- ^ A parser producing 'AST'.
AssignmentParser :: (Bounded grammar, Enum grammar, Eq grammar, Show grammar, Symbol grammar, InUnion fs (Syntax.Error (Error grammar)), Traversable (Union fs), Traversable f)
=> Parser (Cofree f (Record (Maybe grammar ': Location))) -- ^ A parser producing 'AST'.
-> Assignment grammar (Term (Union fs) (Record Location)) -- ^ An assignment from 'AST' onto 'Term's.
-> Parser (Term (Union fs) (Record Location)) -- ^ A parser of 'Term's.
-- | A tree-sitter parser.

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, ScopedTypeVariables #-}
{-# LANGUAGE DataKinds, ScopedTypeVariables, TypeOperators #-}
module TreeSitter
( treeSitterParser
, parseToAST
@ -42,7 +42,7 @@ treeSitterParser language grammar source = bracket ts_document_new ts_document_f
-- | Parse 'Source' with the given 'TS.Language' and return its AST.
parseToAST :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Source -> IO (A.AST grammar)
parseToAST :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Source -> IO (Cofree [] (Record (Maybe grammar ': A.Location)))
parseToAST language source = bracket ts_document_new ts_document_free $ \ document -> do
ts_document_set_language document language
root <- withCStringLen (toText source) $ \ (source, len) -> do
@ -54,7 +54,7 @@ parseToAST language source = bracket ts_document_new ts_document_free $ \ docume
anaM toAST root
toAST :: (Bounded grammar, Enum grammar) => Node -> IO (Base (A.AST grammar) Node)
toAST :: (Bounded grammar, Enum grammar) => Node -> IO (CofreeF [] (Record (Maybe grammar ': A.Location)) Node)
toAST node@Node{..} = do
let count = fromIntegral nodeChildCount
children <- allocaArray count $ \ childNodesPtr -> do