mirror of
https://github.com/github/semantic.git
synced 2024-12-25 16:02:43 +03:00
Merge branch 'master' into go-assignment
This commit is contained in:
commit
d3211a5dd2
@ -59,7 +59,6 @@ library
|
||||
, Language.JSON.Assignment
|
||||
, Language.Ruby.Grammar
|
||||
, Language.Ruby.Assignment
|
||||
, Language.TypeScript
|
||||
, Language.TypeScript.Assignment
|
||||
, Language.TypeScript.Grammar
|
||||
, Language.TypeScript.Syntax
|
||||
@ -72,6 +71,7 @@ library
|
||||
, Renderer.JSON
|
||||
, Renderer.Patch
|
||||
, Renderer.SExpression
|
||||
, Renderer.Tag
|
||||
, Renderer.TOC
|
||||
, RWS
|
||||
, RWS.FeatureVector
|
||||
@ -102,6 +102,7 @@ library
|
||||
, freer-cofreer
|
||||
, ghc-prim
|
||||
, gitrev
|
||||
, Glob
|
||||
, hashable
|
||||
, kdt
|
||||
, mersenne-random-pure64
|
||||
|
@ -5,7 +5,8 @@ import Data.ByteString (ByteString)
|
||||
import Data.ByteString.Lazy (toStrict)
|
||||
import Data.Map (Map)
|
||||
import Data.Semigroup
|
||||
import Data.Text (Text)
|
||||
import Data.Text (Text, intercalate)
|
||||
import Data.Text.Encoding (encodeUtf8)
|
||||
|
||||
class Monoid o => Output o where
|
||||
toOutput :: o -> ByteString
|
||||
@ -13,6 +14,9 @@ class Monoid o => Output o where
|
||||
instance Output ByteString where
|
||||
toOutput s = s
|
||||
|
||||
instance Output [Text] where
|
||||
toOutput = encodeUtf8 . intercalate "\n"
|
||||
|
||||
instance Output (Map Text Value) where
|
||||
toOutput = toStrict . (<> "\n") . encode
|
||||
|
||||
|
@ -4,6 +4,7 @@ module Data.Range
|
||||
, rangeLength
|
||||
, offsetRange
|
||||
, intersectsRange
|
||||
, subtractRange
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
@ -27,6 +28,9 @@ offsetRange a b = Range (start a + b) (end a + b)
|
||||
intersectsRange :: Range -> Range -> Bool
|
||||
intersectsRange range1 range2 = start range1 < end range2 && start range2 < end range1
|
||||
|
||||
subtractRange :: Range -> Range -> Range
|
||||
subtractRange range1 range2 = Range (start range1) (end range1 - rangeLength (Range (start range2) (max (end range1) (end range2))))
|
||||
|
||||
|
||||
-- Instances
|
||||
|
||||
|
@ -23,6 +23,7 @@ module Data.Source
|
||||
, spanToRangeInLineRanges
|
||||
, sourceLineRangesByLineNumber
|
||||
, rangeToSpan
|
||||
, newlineIndices
|
||||
) where
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
@ -103,7 +104,29 @@ sourceLineRanges source = sourceLineRangesWithin (totalRange source) source
|
||||
|
||||
-- | Compute the 'Range's of each line in a 'Range' of a 'Source'.
|
||||
sourceLineRangesWithin :: Range -> Source -> [Range]
|
||||
sourceLineRangesWithin range = uncurry (zipWith Range) . ((start range:) &&& (<> [ end range ])) . fmap (+ succ (start range)) . B.elemIndices (toEnum (ord '\n')) . sourceBytes . slice range
|
||||
sourceLineRangesWithin range = uncurry (zipWith Range)
|
||||
. ((start range:) &&& (<> [ end range ]))
|
||||
. fmap (+ succ (start range))
|
||||
. newlineIndices
|
||||
. sourceBytes
|
||||
. slice range
|
||||
|
||||
-- | Return all indices of newlines ('\n', '\r', and '\r\n') in the 'ByteString'.
|
||||
newlineIndices :: B.ByteString -> [Int]
|
||||
newlineIndices = go 0
|
||||
where go n bs | B.null bs = []
|
||||
| otherwise = case (searchCR bs, searchLF bs) of
|
||||
(Nothing, Nothing) -> []
|
||||
(Just i, Nothing) -> recur n i bs
|
||||
(Nothing, Just i) -> recur n i bs
|
||||
(Just crI, Just lfI)
|
||||
| succ crI == lfI -> recur n lfI bs
|
||||
| otherwise -> recur n (min crI lfI) bs
|
||||
recur n i bs = let j = n + i in j : go (succ j) (B.drop (succ i) bs)
|
||||
searchLF = B.elemIndex (toEnum (ord '\n'))
|
||||
searchCR = B.elemIndex (toEnum (ord '\r'))
|
||||
|
||||
{-# INLINE newlineIndices #-}
|
||||
|
||||
|
||||
-- Conversion
|
||||
|
@ -81,7 +81,7 @@ instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: ![a] }
|
||||
data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: !a }
|
||||
deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Diffable Class where
|
||||
|
19
src/Files.hs
19
src/Files.hs
@ -1,8 +1,11 @@
|
||||
{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, DeriveAnyClass, DuplicateRecordFields, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, DeriveAnyClass, DuplicateRecordFields, ScopedTypeVariables, TupleSections #-}
|
||||
module Files
|
||||
( readFile
|
||||
, isDirectory
|
||||
, readBlobPairsFromHandle
|
||||
, readBlobsFromHandle
|
||||
, readBlobsFromPaths
|
||||
, readBlobsFromDir
|
||||
, languageForFilePath
|
||||
) where
|
||||
|
||||
@ -25,6 +28,8 @@ import Prelude hiding (readFile)
|
||||
import System.Exit
|
||||
import System.FilePath
|
||||
import System.IO (Handle)
|
||||
import System.FilePath.Glob
|
||||
import System.Directory (doesDirectoryExist)
|
||||
import Text.Read
|
||||
|
||||
-- | Read a utf8-encoded file to a 'Blob'.
|
||||
@ -34,6 +39,9 @@ readFile path language = do
|
||||
raw <- liftIO $ (Just <$> B.readFile path) `catch` (const (pure Nothing) :: IOException -> IO (Maybe B.ByteString))
|
||||
pure $ fromMaybe (Blob.emptyBlob path) (Blob.sourceBlob path language . fromBytes <$> raw)
|
||||
|
||||
isDirectory :: MonadIO m => FilePath -> m Bool
|
||||
isDirectory path = liftIO (doesDirectoryExist path) >>= pure
|
||||
|
||||
-- | Return a language based on a FilePath's extension, or Nothing if extension is not found or not supported.
|
||||
languageForFilePath :: FilePath -> Maybe Language
|
||||
languageForFilePath = languageForType . takeExtension
|
||||
@ -51,6 +59,15 @@ readBlobsFromHandle :: MonadIO m => Handle -> m [Blob.Blob]
|
||||
readBlobsFromHandle = fmap toBlobs . readFromHandle
|
||||
where toBlobs BlobParse{..} = fmap toBlob blobs
|
||||
|
||||
readBlobsFromPaths :: MonadIO m => [(FilePath, Maybe Language)] -> m [Blob.Blob]
|
||||
readBlobsFromPaths = traverse (uncurry Files.readFile)
|
||||
|
||||
readBlobsFromDir :: MonadIO m => FilePath -> m [Blob.Blob]
|
||||
readBlobsFromDir path = do
|
||||
paths <- liftIO (globDir1 (compile "[^vendor]**/*[.rb|.js|.tsx|.go|.py]") path)
|
||||
let paths' = catMaybes $ fmap (\p -> (p,) . Just <$> languageForFilePath p) paths
|
||||
traverse (uncurry readFile) paths'
|
||||
|
||||
readFromHandle :: (FromJSON a, MonadIO m) => Handle -> m a
|
||||
readFromHandle h = do
|
||||
input <- liftIO $ BL.hGetContents h
|
||||
|
@ -255,7 +255,7 @@ async' :: Assignment
|
||||
async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> source)
|
||||
|
||||
classDefinition :: Assignment
|
||||
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> manyTerm expression)
|
||||
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions)
|
||||
where argumentList = symbol ArgumentList *> children (manyTerm expression)
|
||||
<|> pure []
|
||||
|
||||
|
@ -202,11 +202,11 @@ endBlock :: Assignment
|
||||
endBlock = makeTerm <$> symbol EndBlock <*> children (Statement.ScopeExit <$> many expression)
|
||||
|
||||
class' :: Assignment
|
||||
class' = makeTerm <$> symbol Class <*> children (Declaration.Class <$> pure [] <*> expression <*> (superclass <|> pure []) <*> many expression)
|
||||
class' = makeTerm <$> symbol Class <*> children (Declaration.Class <$> pure [] <*> expression <*> (superclass <|> pure []) <*> expressions)
|
||||
where superclass = pure <$ symbol Superclass <*> children expression
|
||||
|
||||
singletonClass :: Assignment
|
||||
singletonClass = makeTerm <$> symbol SingletonClass <*> children (Declaration.Class <$> pure [] <*> expression <*> pure [] <*> many expression)
|
||||
singletonClass = makeTerm <$> symbol SingletonClass <*> children (Declaration.Class <$> pure [] <*> expression <*> pure [] <*> expressions)
|
||||
|
||||
module' :: Assignment
|
||||
module' = makeTerm <$> symbol Module <*> children (Declaration.Module <$> expression <*> many expression)
|
||||
|
@ -1,183 +0,0 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Language.TypeScript where
|
||||
|
||||
import Control.Comonad (extract)
|
||||
import Control.Comonad.Cofree (unwrap)
|
||||
import Data.Foldable (toList)
|
||||
import Data.Record
|
||||
import Data.Source
|
||||
import Data.Term
|
||||
import Data.Text (Text)
|
||||
import Info
|
||||
import Language
|
||||
import qualified Syntax as S
|
||||
|
||||
termAssignment
|
||||
:: Source -- ^ The source of the term.
|
||||
-> Category -- ^ The category for the term.
|
||||
-> [ Term S.Syntax (Record DefaultFields) ] -- ^ The child nodes of the term.
|
||||
-> Maybe (S.Syntax (Term S.Syntax (Record DefaultFields))) -- ^ The resulting term, in Maybe.
|
||||
termAssignment _ category children =
|
||||
case (category, children) of
|
||||
(Assignment, [ identifier, value ]) -> Just $ S.Assignment identifier value
|
||||
(MathAssignment, [ identifier, value ]) -> Just $ S.OperatorAssignment identifier value
|
||||
(MemberAccess, [ base, property ]) -> Just $ S.MemberAccess base property
|
||||
(SubscriptAccess, [ base, element ]) -> Just $ S.SubscriptAccess base element
|
||||
(CommaOperator, [ a, b ])
|
||||
| S.Indexed rest <- unwrap b
|
||||
-> Just $ S.Indexed $ a : rest
|
||||
(FunctionCall, id : rest) -> case break ((== Args) . Info.category . extract) rest of
|
||||
(typeArgs, [ args ]) -> let flatArgs = toList (unwrap args) in
|
||||
Just $ case unwrap id of
|
||||
S.MemberAccess target method -> S.MethodCall target method typeArgs flatArgs
|
||||
_ -> S.FunctionCall id typeArgs flatArgs
|
||||
_ -> Nothing
|
||||
(Ternary, condition : cases) -> Just $ S.Ternary condition cases
|
||||
(Other "variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(Other "trailing_variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(Other "lexical_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(VarAssignment, [id, assignment]) -> Just $ S.VarAssignment [id] assignment
|
||||
(FieldDecl, _) -> Just $ S.FieldDecl children
|
||||
(Object, _) -> Just . S.Object Nothing $ foldMap toTuple children
|
||||
(DoWhile, [ expr, body ]) -> Just $ S.DoWhile expr body
|
||||
(Constructor, [ expr ]) -> Just $ S.Constructor expr
|
||||
(Try, [ body ]) -> Just $ S.Try [body] [] Nothing Nothing
|
||||
(Try, [ body, catch ])
|
||||
| Catch <- Info.category (extract catch)
|
||||
-> Just $ S.Try [body] [catch] Nothing Nothing
|
||||
(Try, [ body, finally ])
|
||||
| Finally <- Info.category (extract finally)
|
||||
-> Just $ S.Try [body] [] Nothing (Just finally)
|
||||
(Try, [ body, catch, finally ])
|
||||
| Catch <- Info.category (extract catch)
|
||||
, Finally <- Info.category (extract finally)
|
||||
-> Just $ S.Try [body] [catch] Nothing (Just finally)
|
||||
(ArrayLiteral, _) -> Just $ S.Array Nothing children
|
||||
(Method, children) -> case break ((== ExpressionStatements) . Info.category . extract) children of
|
||||
(prev, [body]) -> case break ((== Identifier) . Info.category . extract) prev of
|
||||
(prev, [id, callSignature]) -> Just $ S.Method prev id Nothing (toList (unwrap callSignature)) (toList (unwrap body))
|
||||
_ -> Nothing -- No identifier found or callSignature found.
|
||||
_ -> Nothing -- No body found.``
|
||||
(Class, identifier : rest) -> case break ((== Other "class_body") . Info.category . extract) rest of
|
||||
(clauses, [ definitions ]) -> Just $ S.Class identifier clauses (toList (unwrap definitions))
|
||||
_ -> Nothing
|
||||
(Module, [ identifier, definitions ]) -> Just $ S.Module identifier (toList (unwrap definitions))
|
||||
(Namespace, [ identifier, definitions ]) -> Just $ S.Namespace identifier (toList (unwrap definitions))
|
||||
(Import, [ statements, identifier ] ) -> Just $ S.Import identifier (toList (unwrap statements))
|
||||
(Import, [ identifier ] ) -> Just $ S.Import identifier []
|
||||
(Export, [ statements, identifier] ) -> Just $ S.Export (Just identifier) (toList (unwrap statements))
|
||||
(Export, [ statements ] )
|
||||
| S.Indexed _ <- unwrap statements
|
||||
-> Just $ S.Export Nothing (toList (unwrap statements))
|
||||
| otherwise -> Just $ S.Export (Just statements) []
|
||||
(For, _:_) -> Just $ S.For (init children >>= flattenExpressionStatements) [last children]
|
||||
(Function, children) -> case break ((== ExpressionStatements) . Info.category . extract) children of
|
||||
(inits, [body]) -> case inits of
|
||||
[id, callSignature] -> Just $ S.Function id (toList (unwrap callSignature)) (toList (unwrap body))
|
||||
[callSignature] -> Just $ S.AnonymousFunction (toList (unwrap callSignature)) (toList (unwrap body))
|
||||
_ -> Nothing -- More than 1 identifier found or no call signature found
|
||||
_ -> Nothing -- No body found.
|
||||
(Ty, children) -> Just $ S.Ty children
|
||||
(Interface, children) -> toInterface children
|
||||
_ -> Nothing
|
||||
where flattenExpressionStatements term
|
||||
| Info.category (extract term) `elem` [ExpressionStatements, CommaOperator] = toList (unwrap term) >>= flattenExpressionStatements
|
||||
| otherwise = [term]
|
||||
|
||||
categoryForTypeScriptName :: Text -> Category
|
||||
categoryForTypeScriptName category = case category of
|
||||
"object" -> Object
|
||||
"expression_statement" -> ExpressionStatements
|
||||
"trailing_expression_statement" -> ExpressionStatements
|
||||
"this_expression" -> Identifier
|
||||
"null" -> Identifier
|
||||
"undefined" -> Identifier
|
||||
"type_identifier" -> Identifier
|
||||
"property_identifier" -> Identifier
|
||||
"shorthand_property_identifier" -> Identifier
|
||||
"nested_identifier" -> Identifier
|
||||
"arrow_function" -> Function
|
||||
"generator_function" -> Function
|
||||
"math_op" -> MathOperator -- math operator, e.g. +, -, *, /.
|
||||
"update_expression" -> MathOperator -- math operator, e.g. ++, --
|
||||
"bool_op" -> BooleanOperator -- boolean operator, e.g. ||, &&.
|
||||
"comma_op" -> CommaOperator -- comma operator, e.g. expr1, expr2.
|
||||
"sequence_expression" -> CommaOperator -- comma operator, e.g. expr1, expr2.
|
||||
"delete_op" -> Operator -- delete operator, e.g. delete x[2].
|
||||
"type_op" -> Operator -- type operator, e.g. typeof Object.
|
||||
"void_op" -> Operator -- void operator, e.g. void 2.
|
||||
"for_statement" -> For
|
||||
"trailing_for_statement" -> For
|
||||
"for_in_statement" -> For
|
||||
"trailing_for_in_statement" -> For
|
||||
"for_of_statement" -> For
|
||||
"trailing_for_of_statement" -> For
|
||||
"new_expression" -> Constructor
|
||||
"class" -> Class
|
||||
"catch" -> Catch
|
||||
"catch_clause" -> Catch
|
||||
"finally" -> Finally
|
||||
"finally_clause" -> Finally
|
||||
"if_statement" -> If
|
||||
"trailing_if_statement" -> If
|
||||
"empty_statement" -> Empty
|
||||
"program" -> Program
|
||||
"function_call" -> FunctionCall
|
||||
"call_expression" -> FunctionCall
|
||||
"pair" -> Pair
|
||||
"string" -> StringLiteral
|
||||
"integer" -> IntegerLiteral
|
||||
"number" -> NumberLiteral
|
||||
"float" -> FloatLiteral
|
||||
"symbol" -> SymbolLiteral
|
||||
"array" -> ArrayLiteral
|
||||
"function" -> Function
|
||||
"identifier" -> Identifier
|
||||
"formal_parameters" -> Params
|
||||
"arguments" -> Args
|
||||
"statement_block" -> ExpressionStatements
|
||||
"assignment" -> Assignment
|
||||
"assignment_expression" -> Assignment
|
||||
"member_access" -> MemberAccess
|
||||
"member_expression" -> MemberAccess
|
||||
"op" -> Operator
|
||||
"subscript_access" -> SubscriptAccess
|
||||
"subscript_expression" -> SubscriptAccess
|
||||
"regex" -> Regex
|
||||
"template_string" -> TemplateString
|
||||
"switch_statement" -> Switch
|
||||
"math_assignment" -> MathAssignment
|
||||
"augmented_assignment_expression" -> MathAssignment
|
||||
"case" -> Case
|
||||
"switch_case" -> Case
|
||||
"true" -> Boolean
|
||||
"false" -> Boolean
|
||||
"ternary" -> Ternary
|
||||
"ternary_expression" -> Ternary
|
||||
"while_statement" -> While
|
||||
"trailing_while_statement" -> While
|
||||
"do_statement" -> DoWhile
|
||||
"trailing_do_statement" -> DoWhile
|
||||
"return_statement" -> Return
|
||||
"trailing_return_statement" -> Return
|
||||
"throw_statement" -> Throw
|
||||
"trailing_throw_statement" -> Throw
|
||||
"try_statement" -> Try
|
||||
"method_definition" -> Method
|
||||
"comment" -> Comment
|
||||
"bitwise_op" -> BitwiseOperator
|
||||
"rel_op" -> RelationalOperator
|
||||
"import_statement" -> Import
|
||||
"export_statement" -> Export
|
||||
"break_statement" -> Break
|
||||
"continue_statement" -> Continue
|
||||
"yield_expression" -> Yield
|
||||
"public_field_definition" -> FieldDecl
|
||||
"variable_declarator" -> VarAssignment
|
||||
"type_annotation" -> Ty
|
||||
"template_chars" -> TemplateString
|
||||
"module" -> Module
|
||||
"internal_module" -> Namespace
|
||||
"interface_declaration" -> Interface
|
||||
"parenthesized_expression" -> ParenthesizedExpression
|
||||
name -> Other name
|
@ -542,9 +542,11 @@ constructorTy = makeTerm <$> symbol ConstructorType <*> children (TypeScript.Syn
|
||||
statementBlock :: Assignment
|
||||
statementBlock = makeTerm <$> symbol StatementBlock <*> children (manyTerm statement)
|
||||
|
||||
classBodyStatements :: Assignment.Assignment [] Grammar [Term]
|
||||
classBodyStatements = symbol ClassBody *> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment))
|
||||
classBodyStatements :: Assignment
|
||||
classBodyStatements = mk <$> symbol ClassBody <*> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment))
|
||||
where
|
||||
mk _ [a] = a
|
||||
mk loc children = makeTerm loc children
|
||||
contextualize' (cs, formalParams) = case nonEmpty cs of
|
||||
Just cs -> toList cs ++ formalParams
|
||||
Nothing -> formalParams
|
||||
|
@ -419,7 +419,7 @@ instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data AbstractClass a = AbstractClass { _abstractClassIdentifier :: !a, _abstractClassTypeParameters :: !a, _classHeritage :: ![a], _classBody :: ![a] }
|
||||
data AbstractClass a = AbstractClass { _abstractClassIdentifier :: !a, _abstractClassTypeParameters :: !a, _classHeritage :: ![a], _classBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 AbstractClass where liftEq = genericLiftEq
|
||||
|
@ -10,6 +10,7 @@ module Renderer
|
||||
, renderJSONTerm
|
||||
, renderToCDiff
|
||||
, renderToCTerm
|
||||
, renderToTags
|
||||
, HasDeclaration
|
||||
, declarationAlgebra
|
||||
, syntaxDeclarationAlgebra
|
||||
@ -25,6 +26,7 @@ import Data.Text (Text)
|
||||
import Renderer.JSON as R
|
||||
import Renderer.Patch as R
|
||||
import Renderer.SExpression as R
|
||||
import Renderer.Tag as R
|
||||
import Renderer.TOC as R
|
||||
|
||||
-- | Specification of renderers for diffs, producing output in the parameter type.
|
||||
@ -35,6 +37,7 @@ data DiffRenderer output where
|
||||
OldToCDiffRenderer :: DiffRenderer Summaries
|
||||
-- | Compute a table of contents for the diff & encode it as JSON (uses the new Assignment parse tree parser).
|
||||
ToCDiffRenderer :: DiffRenderer Summaries
|
||||
|
||||
-- | Render to JSON with the format documented in docs/json-format.md
|
||||
JSONDiffRenderer :: DiffRenderer (Map.Map Text Value)
|
||||
-- | Render to a 'ByteString' formatted as nested s-expressions with patches indicated.
|
||||
@ -51,6 +54,8 @@ data TermRenderer output where
|
||||
JSONTermRenderer :: TermRenderer [Value]
|
||||
-- | Render to a 'ByteString' formatted as nested s-expressions.
|
||||
SExpressionTermRenderer :: TermRenderer ByteString
|
||||
-- | Render to a list of tags.
|
||||
TagsTermRenderer :: TermRenderer [Value]
|
||||
|
||||
deriving instance Eq (TermRenderer output)
|
||||
deriving instance Show (TermRenderer output)
|
||||
|
@ -4,17 +4,20 @@ module Renderer.TOC
|
||||
, renderToCTerm
|
||||
, diffTOC
|
||||
, Summaries(..)
|
||||
, JSONSummary(..)
|
||||
, TOCSummary(..)
|
||||
, isValidSummary
|
||||
, Declaration(..)
|
||||
, getDeclaration
|
||||
, declaration
|
||||
, HasDeclaration
|
||||
, declarationAlgebra
|
||||
, syntaxDeclarationAlgebra
|
||||
, Entry(..)
|
||||
, tableOfContentsBy
|
||||
, termTableOfContentsBy
|
||||
, dedupe
|
||||
, entrySummary
|
||||
, toCategoryName
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
@ -40,7 +43,7 @@ import Data.Record
|
||||
import Data.Semigroup ((<>), sconcat)
|
||||
import Data.Source as Source
|
||||
import Data.Term
|
||||
import Data.Text (toLower)
|
||||
import Data.Text (toLower, stripEnd)
|
||||
import qualified Data.Text as T
|
||||
import Data.Union
|
||||
import GHC.Generics
|
||||
@ -67,8 +70,9 @@ instance Output Summaries where
|
||||
instance ToJSON Summaries where
|
||||
toJSON Summaries{..} = object [ "changes" .= changes, "errors" .= errors ]
|
||||
|
||||
data JSONSummary
|
||||
= JSONSummary
|
||||
|
||||
data TOCSummary
|
||||
= TOCSummary
|
||||
{ summaryCategoryName :: T.Text
|
||||
, summaryTermName :: T.Text
|
||||
, summarySpan :: Span
|
||||
@ -77,21 +81,21 @@ data JSONSummary
|
||||
| ErrorSummary { error :: T.Text, errorSpan :: Span, errorLanguage :: Maybe Language }
|
||||
deriving (Generic, Eq, Show)
|
||||
|
||||
instance ToJSON JSONSummary where
|
||||
toJSON JSONSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= summaryCategoryName, "term" .= summaryTermName, "span" .= summarySpan ]
|
||||
instance ToJSON TOCSummary where
|
||||
toJSON TOCSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= summaryCategoryName, "term" .= summaryTermName, "span" .= summarySpan ]
|
||||
toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan, "language" .= errorLanguage ]
|
||||
|
||||
isValidSummary :: JSONSummary -> Bool
|
||||
isValidSummary :: TOCSummary -> Bool
|
||||
isValidSummary ErrorSummary{} = False
|
||||
isValidSummary _ = True
|
||||
|
||||
-- | A declaration’s identifier and type.
|
||||
data Declaration
|
||||
= MethodDeclaration { declarationIdentifier :: T.Text }
|
||||
| ClassDeclaration { declarationIdentifier :: T.Text }
|
||||
| FunctionDeclaration { declarationIdentifier :: T.Text }
|
||||
| SectionDeclaration { declarationIdentifier :: T.Text, declarationLevel :: Int }
|
||||
| ErrorDeclaration { declarationIdentifier :: T.Text, declarationLanguage :: Maybe Language }
|
||||
= MethodDeclaration { declarationIdentifier :: T.Text, declarationText :: T.Text, declarationLanguage :: Maybe Language, declarationReceiver :: Maybe T.Text }
|
||||
| ClassDeclaration { declarationIdentifier :: T.Text, declarationText :: T.Text, declarationLanguage :: Maybe Language }
|
||||
| FunctionDeclaration { declarationIdentifier :: T.Text, declarationText :: T.Text, declarationLanguage :: Maybe Language }
|
||||
| SectionDeclaration { declarationIdentifier :: T.Text, declarationText :: T.Text, declarationLanguage :: Maybe Language, declarationLevel :: Int }
|
||||
| ErrorDeclaration { declarationIdentifier :: T.Text, declarationText :: T.Text, declarationLanguage :: Maybe Language }
|
||||
deriving (Eq, Generic, Show)
|
||||
|
||||
|
||||
@ -134,40 +138,40 @@ class CustomHasDeclaration syntax where
|
||||
-- | Produce a 'SectionDeclaration' from the first line of the heading of a 'Markdown.Section' node.
|
||||
instance CustomHasDeclaration Markdown.Section where
|
||||
customToDeclaration Blob{..} _ (Markdown.Section level (Term (In headingAnn headingF), _) _)
|
||||
= Just $ SectionDeclaration (maybe (getSource (byteRange headingAnn)) (getSource . sconcat) (nonEmpty (byteRange . termAnnotation . unTerm <$> toList headingF))) level
|
||||
= Just $ SectionDeclaration (maybe (getSource (byteRange headingAnn)) (getSource . sconcat) (nonEmpty (byteRange . termAnnotation . unTerm <$> toList headingF))) mempty blobLanguage level
|
||||
where getSource = firstLine . toText . flip Source.slice blobSource
|
||||
firstLine = T.takeWhile (/= '\n')
|
||||
|
||||
-- | Produce an 'ErrorDeclaration' for 'Syntax.Error' nodes.
|
||||
instance CustomHasDeclaration Syntax.Error where
|
||||
customToDeclaration Blob{..} ann err@Syntax.Error{}
|
||||
= Just $ ErrorDeclaration (T.pack (formatTOCError (Syntax.unError (sourceSpan ann) err))) blobLanguage
|
||||
= Just $ ErrorDeclaration (T.pack (formatTOCError (Syntax.unError (sourceSpan ann) err))) mempty blobLanguage
|
||||
|
||||
-- | Produce a 'FunctionDeclaration' for 'Declaration.Function' nodes so long as their identifier is non-empty (defined as having a non-empty 'byteRange').
|
||||
instance CustomHasDeclaration Declaration.Function where
|
||||
customToDeclaration Blob{..} _ (Declaration.Function _ (Term (In identifierAnn _), _) _ _)
|
||||
customToDeclaration blob@Blob{..} ann decl@(Declaration.Function _ (Term (In identifierAnn _), _) _ _)
|
||||
-- Do not summarize anonymous functions
|
||||
| isEmpty identifierAnn = Nothing
|
||||
-- Named functions
|
||||
| otherwise = Just $ FunctionDeclaration (getSource identifierAnn)
|
||||
| otherwise = Just $ FunctionDeclaration (getSource identifierAnn) (getFunctionSource blob (In ann decl)) blobLanguage
|
||||
where getSource = toText . flip Source.slice blobSource . byteRange
|
||||
isEmpty = (== 0) . rangeLength . byteRange
|
||||
|
||||
-- | Produce a 'MethodDeclaration' for 'Declaration.Method' nodes. If the method’s receiver is non-empty (defined as having a non-empty 'byteRange'), the 'declarationIdentifier' will be formatted as 'receiver.method_name'; otherwise it will be simply 'method_name'.
|
||||
instance CustomHasDeclaration Declaration.Method where
|
||||
customToDeclaration Blob{..} _ (Declaration.Method _ (Term (In receiverAnn _), _) (Term (In identifierAnn _), _) _ _)
|
||||
customToDeclaration blob@Blob{..} ann decl@(Declaration.Method _ (Term (In receiverAnn _), _) (Term (In identifierAnn _), _) _ _)
|
||||
-- Methods without a receiver
|
||||
| isEmpty receiverAnn = Just $ MethodDeclaration (getSource identifierAnn)
|
||||
| isEmpty receiverAnn = Just $ MethodDeclaration (getSource identifierAnn) (getMethodSource blob (In ann decl)) blobLanguage Nothing
|
||||
-- Methods with a receiver (class methods) are formatted like `receiver.method_name`
|
||||
| otherwise = Just $ MethodDeclaration (getSource receiverAnn <> "." <> getSource identifierAnn)
|
||||
| otherwise = Just $ MethodDeclaration (getSource identifierAnn) (getMethodSource blob (In ann decl)) blobLanguage (Just (getSource receiverAnn))
|
||||
where getSource = toText . flip Source.slice blobSource . byteRange
|
||||
isEmpty = (== 0) . rangeLength . byteRange
|
||||
|
||||
-- | Produce a 'ClassDeclaration' for 'Declaration.Class' nodes.
|
||||
instance CustomHasDeclaration Declaration.Class where
|
||||
customToDeclaration Blob{..} _ (Declaration.Class _ (Term (In identifierAnn _), _) _ _)
|
||||
customToDeclaration blob@Blob{..} ann decl@(Declaration.Class _ (Term (In identifierAnn _), _) _ _)
|
||||
-- Classes
|
||||
= Just $ ClassDeclaration (getSource identifierAnn)
|
||||
= Just $ ClassDeclaration (getSource identifierAnn) (getClassSource blob (In ann decl)) blobLanguage
|
||||
where getSource = toText . flip Source.slice blobSource . byteRange
|
||||
|
||||
-- | Produce a 'Declaration' for 'Union's using the 'HasDeclaration' instance & therefore using a 'CustomHasDeclaration' instance when one exists & the type is listed in 'DeclarationStrategy'.
|
||||
@ -219,17 +223,47 @@ declaration (In annotation _) = annotation <$ getDeclaration annotation
|
||||
|
||||
-- | Compute 'Declaration's for methods and functions in 'Syntax'.
|
||||
syntaxDeclarationAlgebra :: HasField fields Range => Blob -> RAlgebra (TermF S.Syntax (Record fields)) (Term S.Syntax (Record fields)) (Maybe Declaration)
|
||||
syntaxDeclarationAlgebra Blob{..} (In a r) = case r of
|
||||
S.Function (identifier, _) _ _ -> Just $ FunctionDeclaration (getSource identifier)
|
||||
S.Method _ (identifier, _) Nothing _ _ -> Just $ MethodDeclaration (getSource identifier)
|
||||
syntaxDeclarationAlgebra blob@Blob{..} decl@(In a r) = case r of
|
||||
S.Function (identifier, _) _ _ -> Just $ FunctionDeclaration (getSource identifier) (getSyntaxDeclarationSource blob decl) blobLanguage
|
||||
S.Method _ (identifier, _) Nothing _ _ -> Just $ MethodDeclaration (getSource identifier) (getSyntaxDeclarationSource blob decl) blobLanguage Nothing
|
||||
S.Method _ (identifier, _) (Just (receiver, _)) _ _
|
||||
| S.Indexed [receiverParams] <- unwrap receiver
|
||||
, S.ParameterDecl (Just ty) _ <- unwrap receiverParams -> Just $ MethodDeclaration ("(" <> getSource ty <> ") " <> getSource identifier)
|
||||
| otherwise -> Just $ MethodDeclaration (getSource receiver <> "." <> getSource identifier)
|
||||
S.ParseError{} -> Just $ ErrorDeclaration (toText (Source.slice (byteRange a) blobSource)) blobLanguage
|
||||
, S.ParameterDecl (Just ty) _ <- unwrap receiverParams -> Just $ MethodDeclaration (getSource identifier) (getSyntaxDeclarationSource blob decl) blobLanguage (Just (getSource ty))
|
||||
| otherwise -> Just $ MethodDeclaration (getSource identifier) (getSyntaxDeclarationSource blob decl) blobLanguage (Just (getSource receiver))
|
||||
S.ParseError{} -> Just $ ErrorDeclaration (toText (Source.slice (byteRange a) blobSource)) mempty blobLanguage
|
||||
_ -> Nothing
|
||||
where getSource = toText . flip Source.slice blobSource . byteRange . extract
|
||||
where
|
||||
getSource = toText . flip Source.slice blobSource . byteRange . extract
|
||||
|
||||
getMethodSource :: HasField fields Range => Blob -> TermF Declaration.Method (Record fields) (Term syntax (Record fields), a) -> T.Text
|
||||
getMethodSource Blob{..} (In a r)
|
||||
= let declRange = byteRange a
|
||||
bodyRange = byteRange <$> case r of
|
||||
Declaration.Method _ _ _ _ (Term (In a' _), _) -> Just a'
|
||||
in maybe mempty (stripEnd . toText . flip Source.slice blobSource . subtractRange declRange) bodyRange
|
||||
|
||||
getFunctionSource :: HasField fields Range => Blob -> TermF Declaration.Function (Record fields) (Term syntax (Record fields), a) -> T.Text
|
||||
getFunctionSource Blob{..} (In a r)
|
||||
= let declRange = byteRange a
|
||||
bodyRange = byteRange <$> case r of
|
||||
Declaration.Function _ _ _ (Term (In a' _), _) -> Just a'
|
||||
in maybe mempty (stripEnd . toText . flip Source.slice blobSource . subtractRange declRange) bodyRange
|
||||
|
||||
getClassSource :: (HasField fields Range) => Blob -> TermF Declaration.Class (Record fields) (Term syntax (Record fields), a) -> T.Text
|
||||
getClassSource Blob{..} (In a r)
|
||||
= let declRange = byteRange a
|
||||
bodyRange = byteRange <$> case r of
|
||||
Declaration.Class _ _ _ (Term (In a' _), _) -> Just a'
|
||||
in maybe mempty (stripEnd . toText . flip Source.slice blobSource . subtractRange declRange) bodyRange
|
||||
|
||||
getSyntaxDeclarationSource :: HasField fields Range => Blob -> TermF Syntax (Record fields) (Term syntax (Record fields), a) -> T.Text
|
||||
getSyntaxDeclarationSource Blob{..} (In a r)
|
||||
= let declRange = byteRange a
|
||||
bodyRange = byteRange <$> case r of
|
||||
S.Function _ _ ((Term (In a' _), _) : _) -> Just a'
|
||||
S.Method _ _ _ _ ((Term (In a' _), _) : _) -> Just a'
|
||||
_ -> Nothing
|
||||
in maybe mempty (stripEnd . toText . flip Source.slice blobSource . subtractRange declRange) bodyRange
|
||||
|
||||
formatTOCError :: Error.Error String -> String
|
||||
formatTOCError e = showExpectation False (errorExpected e) (errorActual e) ""
|
||||
@ -261,7 +295,7 @@ termTableOfContentsBy :: (Foldable f, Functor f)
|
||||
-> Term f annotation
|
||||
-> [a]
|
||||
termTableOfContentsBy selector = cata termAlgebra
|
||||
where termAlgebra r | Just a <- selector r = [a]
|
||||
where termAlgebra r | Just a <- selector r = a : fold r
|
||||
| otherwise = fold r
|
||||
|
||||
|
||||
@ -292,20 +326,24 @@ dedupe = let tuples = sortOn fst . Map.elems . snd . foldl' go (0, Map.empty) in
|
||||
dedupeKey entry = DedupeKey ((fmap toCategoryName . getDeclaration . entryPayload) entry, (fmap (toLower . declarationIdentifier) . getDeclaration . entryPayload) entry)
|
||||
exactMatch = (==) `on` (getDeclaration . entryPayload)
|
||||
|
||||
-- | Construct a 'JSONSummary' from an 'Entry'.
|
||||
entrySummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Entry (Record fields) -> Maybe JSONSummary
|
||||
-- | Construct a 'TOCSummary' from an 'Entry'.
|
||||
entrySummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Entry (Record fields) -> Maybe TOCSummary
|
||||
entrySummary entry = case entry of
|
||||
Changed a -> recordSummary a "modified"
|
||||
Deleted a -> recordSummary a "removed"
|
||||
Inserted a -> recordSummary a "added"
|
||||
Replaced a -> recordSummary a "modified"
|
||||
Changed a -> recordSummary "modified" a
|
||||
Deleted a -> recordSummary "removed" a
|
||||
Inserted a -> recordSummary "added" a
|
||||
Replaced a -> recordSummary "modified" a
|
||||
|
||||
-- | Construct a 'JSONSummary' from a node annotation and a change type label.
|
||||
recordSummary :: (HasField fields (Maybe Declaration), HasField fields Span) => Record fields -> T.Text -> Maybe JSONSummary
|
||||
recordSummary record = case getDeclaration record of
|
||||
Just (ErrorDeclaration text language) -> Just . const (ErrorSummary text (sourceSpan record) language)
|
||||
Just declaration -> Just . JSONSummary (toCategoryName declaration) (declarationIdentifier declaration) (sourceSpan record)
|
||||
Nothing -> const Nothing
|
||||
-- | Construct a 'TOCSummary' from a node annotation and a change type label.
|
||||
recordSummary :: (HasField fields (Maybe Declaration), HasField fields Span) => T.Text -> Record fields -> Maybe TOCSummary
|
||||
recordSummary changeText record = case getDeclaration record of
|
||||
Just (ErrorDeclaration text _ language) -> Just $ ErrorSummary text (sourceSpan record) language
|
||||
Just declaration -> Just $ TOCSummary (toCategoryName declaration) (formatIdentifier declaration) (sourceSpan record) changeText
|
||||
Nothing -> Nothing
|
||||
where
|
||||
formatIdentifier (MethodDeclaration identifier _ (Just Language.Go) (Just receiver)) = "(" <> receiver <> ") " <> identifier
|
||||
formatIdentifier (MethodDeclaration identifier _ _ (Just receiver)) = receiver <> "." <> identifier
|
||||
formatIdentifier declaration = declarationIdentifier declaration
|
||||
|
||||
renderToCDiff :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Both Blob -> Diff f (Record fields) (Record fields) -> Summaries
|
||||
renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC
|
||||
@ -317,22 +355,23 @@ renderToCDiff blobs = uncurry Summaries . bimap toMap toMap . List.partition isV
|
||||
| before == after -> after
|
||||
| otherwise -> before <> " -> " <> after
|
||||
|
||||
renderToCTerm :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Blob -> Term f (Record fields) -> Summaries
|
||||
renderToCTerm Blob{..} = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . termToC
|
||||
where toMap [] = mempty
|
||||
toMap as = Map.singleton (T.pack blobPath) (toJSON <$> as)
|
||||
|
||||
diffTOC :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Diff f (Record fields) (Record fields) -> [JSONSummary]
|
||||
diffTOC :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Diff f (Record fields) (Record fields) -> [TOCSummary]
|
||||
diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration
|
||||
|
||||
termToC :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Term f (Record fields) -> [JSONSummary]
|
||||
termToC = mapMaybe (flip recordSummary "unchanged") . termTableOfContentsBy declaration
|
||||
renderToCTerm :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Blob -> Term f (Record fields) -> Summaries
|
||||
renderToCTerm Blob{..} = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . termToC
|
||||
where
|
||||
toMap [] = mempty
|
||||
toMap as = Map.singleton (T.pack blobPath) (toJSON <$> as)
|
||||
|
||||
termToC :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Term f (Record fields) -> [TOCSummary]
|
||||
termToC = mapMaybe (recordSummary "unchanged") . termTableOfContentsBy declaration
|
||||
|
||||
-- The user-facing category name
|
||||
toCategoryName :: Declaration -> T.Text
|
||||
toCategoryName declaration = case declaration of
|
||||
FunctionDeclaration _ -> "Function"
|
||||
ClassDeclaration _ -> "Class"
|
||||
MethodDeclaration _ -> "Method"
|
||||
SectionDeclaration _ l -> "Heading " <> T.pack (show l)
|
||||
ClassDeclaration{} -> "Class"
|
||||
FunctionDeclaration{} -> "Function"
|
||||
MethodDeclaration{} -> "Method"
|
||||
SectionDeclaration _ _ _ l -> "Heading " <> T.pack (show l)
|
||||
ErrorDeclaration{} -> "ParseError"
|
||||
|
46
src/Renderer/Tag.hs
Normal file
46
src/Renderer/Tag.hs
Normal file
@ -0,0 +1,46 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Renderer.Tag
|
||||
( renderToTags
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Blob
|
||||
import Data.Maybe (mapMaybe)
|
||||
import Data.Record
|
||||
import Data.Term
|
||||
import GHC.Generics
|
||||
import Info
|
||||
import qualified Data.Text as T
|
||||
import Renderer.TOC
|
||||
|
||||
-- | Render a 'Term' to a ctags like output (See 'Tag').
|
||||
renderToTags :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => Blob -> Term f (Record fields) -> [Value]
|
||||
renderToTags Blob{..} = fmap toJSON . termToC blobPath
|
||||
where
|
||||
termToC :: (HasField fields (Maybe Declaration), HasField fields Span, Foldable f, Functor f) => FilePath -> Term f (Record fields) -> [Tag]
|
||||
termToC path = mapMaybe (tagSummary path "unchanged") . termTableOfContentsBy declaration
|
||||
|
||||
-- | Construct a 'Tag' from a node annotation and a change type label.
|
||||
tagSummary :: (HasField fields (Maybe Declaration), HasField fields Span) => FilePath -> T.Text -> Record fields -> Maybe Tag
|
||||
tagSummary path _ record = case getDeclaration record of
|
||||
Just ErrorDeclaration{} -> Nothing
|
||||
Just declaration -> Just $ Tag (declarationIdentifier declaration) (T.pack path) (T.pack . show <$> declarationLanguage declaration) (toCategoryName declaration) (declarationText declaration) (sourceSpan record)
|
||||
_ -> Nothing
|
||||
|
||||
data Tag
|
||||
= Tag { tagSymbol :: T.Text
|
||||
, tagPath :: T.Text
|
||||
, tagLanguage :: Maybe T.Text
|
||||
, tagKind :: T.Text
|
||||
, tagLine :: T.Text
|
||||
, tagSpan :: Span
|
||||
}
|
||||
deriving (Generic, Eq, Show)
|
||||
|
||||
instance ToJSON Tag where
|
||||
toJSON Tag{..} = object [ "symbol" .= tagSymbol
|
||||
, "path" .= tagPath
|
||||
, "language" .= tagLanguage
|
||||
, "kind" .= tagKind
|
||||
, "line" .= tagLine
|
||||
, "span" .= tagSpan ]
|
@ -64,6 +64,12 @@ parseBlob renderer blob@Blob{..} = case (renderer, blobLanguage) of
|
||||
| Just syntaxParser <- lang >>= syntaxParserForLanguage ->
|
||||
parse syntaxParser blob >>= render renderSExpressionTerm . fmap keepCategory
|
||||
|
||||
(TagsTermRenderer, lang)
|
||||
| Just (SomeParser parser) <- lang >>= someParser (Proxy :: Proxy '[HasDeclaration, Foldable, Functor]) ->
|
||||
parse parser blob >>= decorate (declarationAlgebra blob) >>= render (renderToTags blob)
|
||||
| Just syntaxParser <- lang >>= syntaxParserForLanguage ->
|
||||
parse syntaxParser blob >>= decorate (syntaxDeclarationAlgebra blob) >>= render (renderToTags blob)
|
||||
|
||||
_ -> throwError (SomeException (NoParserForLanguage blobPath blobLanguage))
|
||||
|
||||
data NoParserForLanguage = NoParserForLanguage FilePath (Maybe Language.Language)
|
||||
|
@ -32,6 +32,7 @@ import Control.Parallel.Strategies
|
||||
import qualified Control.Concurrent.Async as Async
|
||||
import Control.Monad.Free.Freer
|
||||
import Data.Blob
|
||||
import Data.Bool
|
||||
import qualified Data.ByteString as B
|
||||
import Data.Diff
|
||||
import qualified Data.Error as Error
|
||||
@ -175,7 +176,9 @@ runTaskWithOptions options task = do
|
||||
where
|
||||
go :: Task a -> IO (Either SomeException a)
|
||||
go = iterFreerA (\ task yield -> case task of
|
||||
ReadBlobs source -> (either Files.readBlobsFromHandle (traverse (uncurry Files.readFile)) source >>= yield) `catchError` (pure . Left . toException)
|
||||
ReadBlobs (Left handle) -> (Files.readBlobsFromHandle handle >>= yield) `catchError` (pure . Left . toException)
|
||||
ReadBlobs (Right paths@[(path, Nothing)]) -> (Files.isDirectory path >>= bool (Files.readBlobsFromPaths paths) (Files.readBlobsFromDir path) >>= yield) `catchError` (pure . Left . toException)
|
||||
ReadBlobs (Right paths) -> (Files.readBlobsFromPaths paths >>= yield) `catchError` (pure . Left . toException)
|
||||
ReadBlobPairs source -> (either Files.readBlobPairsFromHandle (traverse (traverse (uncurry Files.readFile))) source >>= yield) `catchError` (pure . Left . toException)
|
||||
WriteToOutput destination contents -> either B.hPutStr B.writeFile destination contents >>= yield
|
||||
WriteLog level message pairs -> queueLogMessage logger level message pairs >>= yield
|
||||
|
@ -62,11 +62,11 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
|
||||
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Show changes between commits or paths"))
|
||||
diffArgumentsParser = runDiff
|
||||
<$> ( flag (SomeRenderer PatchDiffRenderer) (SomeRenderer PatchDiffRenderer) (long "patch" <> help "Output a patch(1)-compatible diff (default)")
|
||||
<|> flag' (SomeRenderer JSONDiffRenderer) (long "json" <> help "Output a json diff")
|
||||
<|> flag' (SomeRenderer SExpressionDiffRenderer) (long "sexpression" <> help "Output an s-expression diff tree")
|
||||
<|> flag' (SomeRenderer OldToCDiffRenderer) (long "toc" <> help "Output a table of contents for a diff")
|
||||
<|> flag' (SomeRenderer ToCDiffRenderer) (long "toc-assignment" <> help "Output a table of contents for a diff using the assignment parser") )
|
||||
<$> ( flag (SomeRenderer PatchDiffRenderer) (SomeRenderer PatchDiffRenderer) (long "patch" <> help "Output patch(1)-compatible diff (default)")
|
||||
<|> flag' (SomeRenderer JSONDiffRenderer) (long "json" <> help "Output JSON diff trees")
|
||||
<|> flag' (SomeRenderer SExpressionDiffRenderer) (long "sexpression" <> help "Output s-expression diff tree")
|
||||
<|> flag' (SomeRenderer OldToCDiffRenderer) (long "toc" <> help "Output JSON table of contents diff summary")
|
||||
<|> flag' (SomeRenderer ToCDiffRenderer) (long "toc-assignment" <> help "Output JSON table of contents diff summary using the assignment parser") )
|
||||
<*> ( Right <$> some (both
|
||||
<$> argument filePathReader (metavar "FILE_A")
|
||||
<*> argument filePathReader (metavar "FILE_B"))
|
||||
@ -76,7 +76,8 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
parseArgumentsParser = runParse
|
||||
<$> ( flag (SomeRenderer SExpressionTermRenderer) (SomeRenderer SExpressionTermRenderer) (long "sexpression" <> help "Output s-expression parse trees (default)")
|
||||
<|> flag' (SomeRenderer JSONTermRenderer) (long "json" <> help "Output JSON parse trees")
|
||||
<|> flag' (SomeRenderer ToCTermRenderer) (long "toc" <> help "Output a table of contents for a file"))
|
||||
<|> flag' (SomeRenderer ToCTermRenderer) (long "toc" <> help "Output JSON table of contents summary")
|
||||
<|> flag' (SomeRenderer TagsTermRenderer) (long "tags" <> help "Output JSON tags/symbols"))
|
||||
<*> ( Right <$> some (argument filePathReader (metavar "FILES..."))
|
||||
<|> pure (Left stdin) )
|
||||
|
||||
|
@ -20,7 +20,6 @@ import Data.Term
|
||||
import Data.Text (Text, pack)
|
||||
import Language
|
||||
import qualified Language.Go as Go
|
||||
import qualified Language.TypeScript as TypeScript
|
||||
import Foreign
|
||||
import Foreign.C.String (peekCString)
|
||||
import Foreign.Marshal.Array (allocaArray)
|
||||
@ -29,7 +28,6 @@ import qualified TreeSitter.Document as TS
|
||||
import qualified TreeSitter.Node as TS
|
||||
import qualified TreeSitter.Language as TS
|
||||
import qualified TreeSitter.Go as TS
|
||||
import qualified TreeSitter.TypeScript as TS
|
||||
import Info
|
||||
|
||||
-- | Returns a TreeSitter parser for the given language and TreeSitter grammar.
|
||||
@ -112,7 +110,6 @@ assignTerm language source annotation children allChildren =
|
||||
where assignTermByLanguage :: Source -> Category -> [ Term S.Syntax (Record DefaultFields) ] -> Maybe (S.Syntax (Term S.Syntax (Record DefaultFields)))
|
||||
assignTermByLanguage = case languageForTSLanguage language of
|
||||
Just Language.Go -> Go.termAssignment
|
||||
Just TypeScript -> TypeScript.termAssignment
|
||||
_ -> \ _ _ _ -> Nothing
|
||||
|
||||
defaultTermAssignment :: Source -> Record DefaultFields -> [ Term S.Syntax (Record DefaultFields) ] -> IO [ Term S.Syntax (Record DefaultFields) ] -> IO (Term S.Syntax (Record DefaultFields))
|
||||
@ -190,12 +187,10 @@ categoryForLanguageProductionName = withDefaults . byLanguage
|
||||
|
||||
byLanguage language = case languageForTSLanguage language of
|
||||
Just Language.Go -> Go.categoryForGoName
|
||||
Just Language.TypeScript -> TypeScript.categoryForTypeScriptName
|
||||
_ -> Other
|
||||
|
||||
|
||||
languageForTSLanguage :: Ptr TS.Language -> Maybe Language
|
||||
languageForTSLanguage = flip lookup
|
||||
[ (TS.tree_sitter_go, Language.Go)
|
||||
, (TS.tree_sitter_typescript, TypeScript)
|
||||
]
|
||||
|
@ -54,6 +54,7 @@ import Renderer.TOC
|
||||
import RWS
|
||||
import Syntax as S
|
||||
import Test.LeanCheck
|
||||
import qualified Language
|
||||
|
||||
type Tier a = [a]
|
||||
|
||||
@ -351,10 +352,17 @@ instance Listable Text where
|
||||
|
||||
instance Listable Declaration where
|
||||
tiers
|
||||
= cons1 (MethodDeclaration)
|
||||
\/ cons1 (FunctionDeclaration)
|
||||
\/ cons1 (flip ErrorDeclaration Nothing)
|
||||
= cons4 MethodDeclaration
|
||||
\/ cons3 FunctionDeclaration
|
||||
\/ cons2 (\ a b -> ErrorDeclaration a b Nothing)
|
||||
|
||||
instance Listable Language.Language where
|
||||
tiers
|
||||
= cons0 Language.Go
|
||||
\/ cons0 Language.JavaScript
|
||||
\/ cons0 Language.Python
|
||||
\/ cons0 Language.Ruby
|
||||
\/ cons0 Language.TypeScript
|
||||
|
||||
instance Listable Range where
|
||||
tiers = cons2 Range
|
||||
|
@ -49,6 +49,20 @@ spec = parallel $ do
|
||||
prop "covers multiple lines" $
|
||||
\ n -> totalSpan (fromText (Text.intersperse '\n' (Text.replicate n "*"))) `shouldBe` Span (Pos 1 1) (Pos (max 1 n) (if n > 0 then 2 else 1))
|
||||
|
||||
describe "newlineIndices" $ do
|
||||
it "finds \\n" $
|
||||
let source = "a\nb" in
|
||||
newlineIndices source `shouldBe` [1]
|
||||
it "finds \\r" $
|
||||
let source = "a\rb" in
|
||||
newlineIndices source `shouldBe` [1]
|
||||
it "finds \\r\\n" $
|
||||
let source = "a\r\nb" in
|
||||
newlineIndices source `shouldBe` [2]
|
||||
it "finds intermixed line endings" $
|
||||
let source = "hi\r}\r}\n xxx \r a" in
|
||||
newlineIndices source `shouldBe` [2, 4, 6, 12]
|
||||
|
||||
prop "preserves characters" . forAll (toTiers (list +| [chr 0xa0..chr 0x24f])) $
|
||||
\ c -> Text.unpack (toText (fromText (Text.singleton c))) `shouldBe` [c]
|
||||
|
||||
|
@ -67,49 +67,49 @@ spec = parallel $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
|
||||
diff <- runTask $ diffWithParser rubyParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||
, JSONSummary "Method" "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified"
|
||||
, JSONSummary "Method" "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed"
|
||||
[ TOCSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||
, TOCSummary "Method" "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified"
|
||||
, TOCSummary "Method" "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed"
|
||||
]
|
||||
|
||||
it "summarizes changed classes" $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/classes.A.rb" "ruby/classes.B.rb")
|
||||
diff <- runTask $ diffWithParser rubyParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Class" "Baz" (sourceSpanBetween (1, 1) (2, 4)) "removed"
|
||||
, JSONSummary "Class" "Foo" (sourceSpanBetween (1, 1) (3, 4)) "modified"
|
||||
, JSONSummary "Class" "Bar" (sourceSpanBetween (5, 1) (6, 4)) "added"
|
||||
[ TOCSummary "Class" "Baz" (sourceSpanBetween (1, 1) (2, 4)) "removed"
|
||||
, TOCSummary "Class" "Foo" (sourceSpanBetween (1, 1) (3, 4)) "modified"
|
||||
, TOCSummary "Class" "Bar" (sourceSpanBetween (5, 1) (6, 4)) "added"
|
||||
]
|
||||
|
||||
it "dedupes changes in same parent method" $ do
|
||||
sourceBlobs <- blobsForPaths (both "javascript/duplicate-parent.A.js" "javascript/duplicate-parent.B.js")
|
||||
diff <- runTask $ diffWithParser typescriptParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Function" "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ]
|
||||
[ TOCSummary "Function" "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ]
|
||||
|
||||
it "dedupes similar methods" $ do
|
||||
sourceBlobs <- blobsForPaths (both "javascript/erroneous-duplicate-method.A.js" "javascript/erroneous-duplicate-method.B.js")
|
||||
diff <- runTask $ diffWithParser typescriptParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Function" "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ]
|
||||
[ TOCSummary "Function" "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ]
|
||||
|
||||
it "summarizes Go methods with receivers with special formatting" $ do
|
||||
sourceBlobs <- blobsForPaths (both "go/method-with-receiver.A.go" "go/method-with-receiver.B.go")
|
||||
diff <- runTask $ diffWithParser goParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Method" "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ]
|
||||
[ TOCSummary "Method" "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ]
|
||||
|
||||
it "summarizes Ruby methods that start with two identifiers" $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/method-starts-with-two-identifiers.A.rb" "ruby/method-starts-with-two-identifiers.B.rb")
|
||||
diff <- runTask $ diffWithParser rubyParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ]
|
||||
[ TOCSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ]
|
||||
|
||||
it "handles unicode characters in file" $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/unicode.A.rb" "ruby/unicode.B.rb")
|
||||
diff <- runTask $ diffWithParser rubyParser sourceBlobs
|
||||
diffTOC diff `shouldBe`
|
||||
[ JSONSummary "Method" "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
|
||||
[ TOCSummary "Method" "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ]
|
||||
|
||||
it "properly slices source blob that starts with a newline and has multi-byte chars" $ do
|
||||
sourceBlobs <- blobsForPaths (both "javascript/starts-with-newline.js" "javascript/starts-with-newline.js")
|
||||
@ -145,13 +145,13 @@ spec = parallel $ do
|
||||
\a -> let term = defaultFeatureVectorDecorator (Info.category . termAnnotation) (a :: Term') in
|
||||
diffTOC (diffSyntaxTerms term term) `shouldBe` []
|
||||
|
||||
describe "JSONSummary" $ do
|
||||
describe "TOCSummary" $ do
|
||||
it "encodes modified summaries to JSON" $ do
|
||||
let summary = JSONSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified"
|
||||
let summary = TOCSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified"
|
||||
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}"
|
||||
|
||||
it "encodes added summaries to JSON" $ do
|
||||
let summary = JSONSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||
let summary = TOCSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}"
|
||||
|
||||
describe "diff with ToCDiffRenderer'" $ do
|
||||
@ -186,14 +186,14 @@ numTocSummaries diff = length $ filter isValidSummary (diffTOC diff)
|
||||
programWithChange :: Term' -> Diff'
|
||||
programWithChange body = merge (programInfo, programInfo) (Indexed [ function' ])
|
||||
where
|
||||
function' = merge ((Just (FunctionDeclaration "foo") :. functionInfo, Just (FunctionDeclaration "foo") :. functionInfo)) (S.Function name' [] [ inserting body ])
|
||||
function' = merge ((Just (FunctionDeclaration "foo" mempty Nothing) :. functionInfo, Just (FunctionDeclaration "foo" mempty Nothing) :. functionInfo)) (S.Function name' [] [ inserting body ])
|
||||
name' = let info = Nothing :. Range 0 0 :. C.Identifier :. sourceSpanBetween (0,0) (0,0) :. Nil in merge (info, info) (Leaf "foo")
|
||||
|
||||
-- Return a diff where term is inserted in the program, below a function found on both sides of the diff.
|
||||
programWithChangeOutsideFunction :: Term' -> Diff'
|
||||
programWithChangeOutsideFunction term = merge (programInfo, programInfo) (Indexed [ function', term' ])
|
||||
where
|
||||
function' = merge (Just (FunctionDeclaration "foo") :. functionInfo, Just (FunctionDeclaration "foo") :. functionInfo) (S.Function name' [] [])
|
||||
function' = merge (Just (FunctionDeclaration "foo" mempty Nothing) :. functionInfo, Just (FunctionDeclaration "foo" mempty Nothing) :. functionInfo) (S.Function name' [] [])
|
||||
name' = let info = Nothing :. Range 0 0 :. C.Identifier :. sourceSpanBetween (0,0) (0,0) :. Nil in merge (info, info) (Leaf "foo")
|
||||
term' = inserting term
|
||||
|
||||
@ -210,7 +210,7 @@ programOf :: Diff' -> Diff'
|
||||
programOf diff = merge (programInfo, programInfo) (Indexed [ diff ])
|
||||
|
||||
functionOf :: Text -> Term' -> Term'
|
||||
functionOf name body = Term $ (Just (FunctionDeclaration name) :. functionInfo) `In` S.Function name' [] [body]
|
||||
functionOf name body = Term $ (Just (FunctionDeclaration name mempty Nothing) :. functionInfo) `In` S.Function name' [] [body]
|
||||
where
|
||||
name' = Term $ (Nothing :. Range 0 0 :. C.Identifier :. sourceSpanBetween (0,0) (0,0) :. Nil) `In` Leaf name
|
||||
|
||||
|
3
test/fixtures/javascript/class.diffA-B.txt
vendored
3
test/fixtures/javascript/class.diffA-B.txt
vendored
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
{+(Method
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
@ -108,4 +109,4 @@
|
||||
{-(Empty)-})-})-}
|
||||
{-(
|
||||
{-(Return
|
||||
{-(Identifier)-})-})-})-}))
|
||||
{-(Identifier)-})-})-})-})))
|
||||
|
3
test/fixtures/javascript/class.diffB-A.txt
vendored
3
test/fixtures/javascript/class.diffB-A.txt
vendored
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
{+(PublicFieldDefinition
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
@ -60,4 +61,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
3
test/fixtures/javascript/class.parseA.txt
vendored
3
test/fixtures/javascript/class.parseA.txt
vendored
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -57,4 +58,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
3
test/fixtures/javascript/class.parseB.txt
vendored
3
test/fixtures/javascript/class.parseB.txt
vendored
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(Method
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -51,4 +52,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
@ -3,6 +3,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(Identifier)+}
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
{ (Identifier)
|
||||
@ -12,14 +13,16 @@
|
||||
(Return
|
||||
{ (Identifier)
|
||||
->(Empty) })))
|
||||
(Empty)))
|
||||
(Empty))))
|
||||
{-(Class
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(NoOp
|
||||
{-(Empty)-})-})-}
|
||||
{-(Empty)-})-})-})-}
|
||||
(Class
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
{ (Identifier)
|
||||
@ -29,4 +32,4 @@
|
||||
(Return
|
||||
{ (Empty)
|
||||
->(Identifier) })))
|
||||
(Empty))))
|
||||
(Empty)))))
|
||||
|
@ -3,6 +3,7 @@
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{-(Identifier)-}
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
{ (Identifier)
|
||||
@ -12,14 +13,16 @@
|
||||
(Return
|
||||
{ (Empty)
|
||||
->(Identifier) })))
|
||||
(Empty)))
|
||||
(Empty))))
|
||||
{+(Class
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(NoOp
|
||||
{+(Empty)+})+})+}
|
||||
{+(Empty)+})+})+})+}
|
||||
(Class
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
{ (Identifier)
|
||||
@ -29,4 +32,4 @@
|
||||
(Return
|
||||
{ (Identifier)
|
||||
->(Empty) })))
|
||||
(Empty))))
|
||||
(Empty)))))
|
||||
|
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
(Identifier)
|
||||
@ -8,14 +9,16 @@
|
||||
(
|
||||
(Return
|
||||
(Identifier))))
|
||||
(Empty)))
|
||||
(Empty))))
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(NoOp
|
||||
(Empty)))
|
||||
(Empty))))
|
||||
(Class
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
(Identifier)
|
||||
@ -23,4 +26,4 @@
|
||||
(
|
||||
(Return
|
||||
(Empty))))
|
||||
(Empty))))
|
||||
(Empty)))))
|
||||
|
@ -2,6 +2,7 @@
|
||||
(Class
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
(Identifier)
|
||||
@ -9,9 +10,10 @@
|
||||
(
|
||||
(Return
|
||||
(Empty))))
|
||||
(Empty)))
|
||||
(Empty))))
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(Annotation
|
||||
(Function
|
||||
(Identifier)
|
||||
@ -19,4 +21,4 @@
|
||||
(
|
||||
(Return
|
||||
(Identifier))))
|
||||
(Empty))))
|
||||
(Empty)))))
|
||||
|
@ -6,6 +6,7 @@
|
||||
(Class
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
@ -67,4 +68,4 @@
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Empty)+}) })))))))
|
||||
{+(Empty)+}) }))))))))
|
||||
|
@ -6,6 +6,7 @@
|
||||
(Class
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
@ -69,4 +70,4 @@
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Empty)+})+})+})+}) })))))))
|
||||
{+(Empty)+})+})+})+}) }))))))))
|
||||
|
@ -5,6 +5,7 @@
|
||||
(Identifier))
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
@ -52,4 +53,4 @@
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty))))))))))))
|
||||
(Empty)))))))))))))
|
||||
|
@ -5,6 +5,7 @@
|
||||
(Identifier))
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(Decorator
|
||||
(ScopeResolution
|
||||
(Identifier))
|
||||
@ -34,4 +35,4 @@
|
||||
(Identifier)
|
||||
(
|
||||
(Identifier)))
|
||||
(Empty)))))))))
|
||||
(Empty))))))))))
|
||||
|
3
test/fixtures/ruby/class.diffA-B.txt
vendored
3
test/fixtures/ruby/class.diffA-B.txt
vendored
@ -9,4 +9,5 @@
|
||||
{-(Class
|
||||
{-(ScopeResolution
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-})-})
|
||||
{-(Identifier)-})-}
|
||||
{-([])-})-})
|
||||
|
3
test/fixtures/ruby/class.diffB-A.txt
vendored
3
test/fixtures/ruby/class.diffB-A.txt
vendored
@ -9,4 +9,5 @@
|
||||
{+(Class
|
||||
{+(ScopeResolution
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+})+})
|
||||
{+(Identifier)+})+}
|
||||
{+([])+})+})
|
||||
|
3
test/fixtures/ruby/class.parseA.txt
vendored
3
test/fixtures/ruby/class.parseA.txt
vendored
@ -9,4 +9,5 @@
|
||||
(Class
|
||||
(ScopeResolution
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Identifier))
|
||||
([])))
|
||||
|
@ -1,16 +1,19 @@
|
||||
(Program
|
||||
{+(AmbientDeclaration
|
||||
{+(InternalModule
|
||||
{+(Identifier)+})+})+}
|
||||
(AmbientDeclaration
|
||||
{ (Class
|
||||
{-(Identifier)-}
|
||||
{-(PublicFieldDefinition
|
||||
(Class
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (PublicFieldDefinition
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Annotation
|
||||
{-(TypeIdentifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})
|
||||
->(InternalModule
|
||||
{+(Identifier)+}) })
|
||||
{-(Empty)-})
|
||||
->([]) }))
|
||||
(AmbientDeclaration
|
||||
{ (VariableDeclaration
|
||||
{-(Assignment
|
||||
@ -18,14 +21,11 @@
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})
|
||||
->(Class
|
||||
{+(Identifier)+}) })
|
||||
{+(AmbientDeclaration
|
||||
{+(InterfaceDeclaration
|
||||
->(InterfaceDeclaration
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(ObjectType)+})+})+}
|
||||
{+(ObjectType)+}) })
|
||||
{-(AmbientDeclaration
|
||||
{-(AmbientFunction
|
||||
{-(Empty)-}
|
||||
@ -99,6 +99,7 @@
|
||||
(AmbientDeclaration
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -126,7 +127,7 @@
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier))))
|
||||
(Identifier)))))
|
||||
{+(AmbientDeclaration
|
||||
{+(AmbientFunction
|
||||
{+(Empty)+}
|
||||
|
@ -1,8 +1,6 @@
|
||||
(Program
|
||||
(AmbientDeclaration
|
||||
{ (InternalModule
|
||||
{-(Identifier)-})
|
||||
->(Class
|
||||
{+(AmbientDeclaration
|
||||
{+(Class
|
||||
{+(Identifier)+}
|
||||
{+(PublicFieldDefinition
|
||||
{+(Empty)+}
|
||||
@ -10,16 +8,14 @@
|
||||
{+(Annotation
|
||||
{+(TypeIdentifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}) })
|
||||
(AmbientDeclaration
|
||||
{ (Class
|
||||
{-(Identifier)-})
|
||||
->(VariableDeclaration
|
||||
{+(Empty)+})+})+})+}
|
||||
{+(AmbientDeclaration
|
||||
{+(VariableDeclaration
|
||||
{+(Assignment
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}) })
|
||||
{+(Empty)+})+})+})+}
|
||||
{+(AmbientDeclaration
|
||||
{+(AmbientFunction
|
||||
{+(Empty)+}
|
||||
@ -34,13 +30,8 @@
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
(AmbientDeclaration
|
||||
{ (InterfaceDeclaration
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(ObjectType)-})
|
||||
->(InternalModule
|
||||
{+(AmbientDeclaration
|
||||
{+(InternalModule
|
||||
{+(Identifier)+}
|
||||
{+(AmbientFunction
|
||||
{+(Empty)+}
|
||||
@ -94,10 +85,24 @@
|
||||
{+(Empty)+}
|
||||
{+(Annotation
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+})+})+})+}) })
|
||||
{+(Identifier)+})+})+})+})+})+}
|
||||
{-(AmbientDeclaration
|
||||
{-(InternalModule
|
||||
{-(Identifier)-})-})-}
|
||||
{-(AmbientDeclaration
|
||||
{-(Class
|
||||
{-(Identifier)-}
|
||||
{-([])-})-})-}
|
||||
{-(AmbientDeclaration
|
||||
{-(InterfaceDeclaration
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(ObjectType)-})-})-}
|
||||
(AmbientDeclaration
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -125,7 +130,7 @@
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier))))
|
||||
(Identifier)))))
|
||||
{-(AmbientDeclaration
|
||||
{-(AmbientFunction
|
||||
{-(Empty)-}
|
||||
|
@ -89,6 +89,7 @@
|
||||
(AmbientDeclaration
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -116,4 +117,4 @@
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier)))))
|
||||
(Identifier))))))
|
||||
|
@ -4,7 +4,8 @@
|
||||
(Identifier)))
|
||||
(AmbientDeclaration
|
||||
(Class
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
([])))
|
||||
(AmbientDeclaration
|
||||
(InterfaceDeclaration
|
||||
(Empty)
|
||||
@ -14,6 +15,7 @@
|
||||
(AmbientDeclaration
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(MethodSignature
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -41,7 +43,7 @@
|
||||
(Empty)
|
||||
(Annotation
|
||||
(PredefinedType))
|
||||
(Identifier))))
|
||||
(Identifier)))))
|
||||
(AmbientDeclaration
|
||||
(AmbientFunction
|
||||
(Empty)
|
||||
|
@ -26,4 +26,5 @@
|
||||
{+(ShorthandPropertyIdentifier)+}
|
||||
{+(ShorthandPropertyIdentifier)+})+})+})+})+}
|
||||
{-(Class
|
||||
{-(Identifier)-})-}))
|
||||
{-(Identifier)-}
|
||||
{-([])-})-}))
|
||||
|
@ -1,7 +1,8 @@
|
||||
(Program
|
||||
(Export
|
||||
{+(Class
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+([])+})+}
|
||||
{-(Function
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
|
@ -1,4 +1,5 @@
|
||||
(Program
|
||||
(Export
|
||||
(Class
|
||||
(Identifier))))
|
||||
(Identifier)
|
||||
([]))))
|
||||
|
3
test/fixtures/typescript/class.diffA-B.txt
vendored
3
test/fixtures/typescript/class.diffA-B.txt
vendored
@ -10,6 +10,7 @@
|
||||
(ExtendsClause
|
||||
{ (TypeIdentifier)
|
||||
->(TypeIdentifier) })
|
||||
(
|
||||
{+(Method
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
@ -117,4 +118,4 @@
|
||||
{-(Empty)-})-})-}
|
||||
{-(
|
||||
{-(Return
|
||||
{-(Identifier)-})-})-})-}))
|
||||
{-(Identifier)-})-})-})-})))
|
||||
|
3
test/fixtures/typescript/class.diffB-A.txt
vendored
3
test/fixtures/typescript/class.diffB-A.txt
vendored
@ -10,6 +10,7 @@
|
||||
(ExtendsClause
|
||||
{ (TypeIdentifier)
|
||||
->(TypeIdentifier) })
|
||||
(
|
||||
{+(PublicFieldDefinition
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
@ -69,4 +70,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
3
test/fixtures/typescript/class.parseA.txt
vendored
3
test/fixtures/typescript/class.parseA.txt
vendored
@ -7,6 +7,7 @@
|
||||
(Identifier)
|
||||
(ExtendsClause
|
||||
(TypeIdentifier))
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -63,4 +64,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
3
test/fixtures/typescript/class.parseB.txt
vendored
3
test/fixtures/typescript/class.parseB.txt
vendored
@ -7,6 +7,7 @@
|
||||
(Identifier)
|
||||
(ExtendsClause
|
||||
(TypeIdentifier))
|
||||
(
|
||||
(Method
|
||||
(Empty)
|
||||
(Empty)
|
||||
@ -57,4 +58,4 @@
|
||||
(Empty)))
|
||||
(
|
||||
(Return
|
||||
(Identifier))))))
|
||||
(Identifier)))))))
|
||||
|
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Readonly)
|
||||
@ -82,4 +83,4 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })))
|
||||
->(Float) }))))
|
||||
|
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Readonly)
|
||||
@ -82,4 +83,4 @@
|
||||
(Empty)
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })))
|
||||
->(Float) }))))
|
||||
|
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Readonly)
|
||||
@ -72,4 +73,4 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Float))))
|
||||
(Float)))))
|
||||
|
@ -1,6 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Identifier)
|
||||
(
|
||||
(PublicFieldDefinition
|
||||
(Empty)
|
||||
(Readonly)
|
||||
@ -73,4 +74,4 @@
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Float))))
|
||||
(Float)))))
|
||||
|
Loading…
Reference in New Issue
Block a user