1
1
mirror of https://github.com/github/semantic.git synced 2024-12-19 12:51:52 +03:00

Merge branch 'master' into unbiased-branch-diff-tests-that-actually-test-branch-diff-bias

This commit is contained in:
Rob Rix 2016-08-12 13:52:03 -04:00 committed by GitHub
commit 08835f5a36
7 changed files with 15 additions and 2 deletions

View File

@ -60,6 +60,8 @@ data Category
| VarDecl | VarDecl
-- | A switch expression. -- | A switch expression.
| Switch | Switch
-- | A if/else expression.
| If
-- | A for expression. -- | A for expression.
| For | For
-- | A while expression. -- | A while expression.

View File

@ -98,6 +98,7 @@ toTermName source term = case unwrap term of
S.Pair a b -> toTermName' a <> ": " <> toTermName' b S.Pair a b -> toTermName' a <> ": " <> toTermName' b
S.Return expr -> maybe "empty" toTermName' expr S.Return expr -> maybe "empty" toTermName' expr
S.Error _ _ -> termNameFromSource term S.Error _ _ -> termNameFromSource term
S.If expr _ _ -> termNameFromSource expr
S.For _ _ -> termNameFromChildren term S.For _ _ -> termNameFromChildren term
S.While expr _ -> toTermName' expr S.While expr _ -> toTermName' expr
S.DoWhile _ expr -> toTermName' expr S.DoWhile _ expr -> toTermName' expr
@ -211,6 +212,7 @@ instance HasCategory Category where
C.Finally -> "finally statement" C.Finally -> "finally statement"
C.Class -> "class" C.Class -> "class"
C.Method -> "method" C.Method -> "method"
C.If -> "if statement"
instance (HasCategory leaf, HasField fields Category) => HasCategory (Term leaf (Record fields)) where instance (HasCategory leaf, HasField fields Category) => HasCategory (Term leaf (Record fields)) where
toCategoryName = toCategoryName . category . extract toCategoryName = toCategoryName . category . extract

View File

@ -9,7 +9,7 @@ import Info
import qualified Syntax as S import qualified Syntax as S
import Term import Term
import qualified Data.Set as Set import qualified Data.Set as Set
import Source import Source hiding (uncons)
import SourceSpan import SourceSpan
-- | A function that takes a source blob and returns an annotated AST. -- | A function that takes a source blob and returns an annotated AST.
@ -91,6 +91,11 @@ termConstructor source sourceSpan info = cofree . construct
construct children | Pair == (category info) = withDefaultInfo $ S.Fixed children construct children | Pair == (category info) = withDefaultInfo $ S.Fixed children
construct children | C.Error == category info = construct children | C.Error == category info =
withDefaultInfo $ S.Error sourceSpan children withDefaultInfo $ S.Error sourceSpan children
construct children | If == category info, Just (expr, clauses) <- uncons children =
withDefaultInfo $ case clauses of
[clause1, clause2] -> S.If expr clause1 (Just clause2)
[clause] -> S.If expr clause Nothing
_ -> S.Error sourceSpan children
construct children | For == category info, Just (exprs, body) <- unsnoc children = construct children | For == category info, Just (exprs, body) <- unsnoc children =
withDefaultInfo $ S.For exprs body withDefaultInfo $ S.For exprs body
construct children | While == category info, [expr, body] <- children = construct children | While == category info, [expr, body] <- children =

View File

@ -71,6 +71,7 @@ termFields info syntax = "range" .= characterRange info : "category" .= category
S.Args c -> childrenFields c S.Args c -> childrenFields c
S.Assignment assignmentId property -> [ "assignmentIdentifier" .= assignmentId ] <> [ "property" .= property ] S.Assignment assignmentId property -> [ "assignmentIdentifier" .= assignmentId ] <> [ "property" .= property ]
S.MemberAccess memberId value -> [ "memberIdentifier" .= memberId ] <> [ "value" .= value ] S.MemberAccess memberId value -> [ "memberIdentifier" .= memberId ] <> [ "value" .= value ]
S.If expr clause maybeClause -> [ "if" .= expr ] <> [ "ifBody" .= clause ] <> [ "elseBody" .= maybeClause ]
S.For exprs body -> [ "forExpressions" .= exprs ] <> [ "forBody" .= body ] S.For exprs body -> [ "forExpressions" .= exprs ] <> [ "forBody" .= body ]
S.While expr body -> [ "whileExpr" .= expr ] <> [ "whileBody" .= body ] S.While expr body -> [ "whileExpr" .= expr ] <> [ "whileBody" .= body ]
S.DoWhile expr body -> [ "doWhileExpr" .= expr ] <> [ "doWhileBody" .= body ] S.DoWhile expr body -> [ "doWhileExpr" .= expr ] <> [ "doWhileBody" .= body ]

View File

@ -72,6 +72,7 @@ styleName category = "category-" <> case category of
ArrayLiteral -> "array" ArrayLiteral -> "array"
C.Class -> "class_statement" C.Class -> "class_statement"
C.Method -> "method" C.Method -> "method"
C.If -> "if_statement"
Other string -> string Other string -> string
-- | Pick the class name for a split patch. -- | Pick the class name for a split patch.
@ -83,7 +84,7 @@ splitPatchToClassName patch = stringValue $ "patch " <> case patch of
-- | Render a diff as an HTML split diff. -- | Render a diff as an HTML split diff.
split :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Renderer (Record fields) split :: (HasField fields Category, HasField fields Cost, HasField fields Range) => Renderer (Record fields)
split blobs diff = SplitOutput $ TL.toStrict . renderHtml split blobs diff = SplitOutput . TL.toStrict . renderHtml
. docTypeHtml . docTypeHtml
. ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>)
. body . body

View File

@ -69,6 +69,7 @@ data Syntax a f
| Class f (Maybe f) [f] | Class f (Maybe f) [f]
-- | A method definition with an identifier, params, and a list of expressions. -- | A method definition with an identifier, params, and a list of expressions.
| Method f [f] [f] | Method f [f] [f]
| If f f (Maybe f)
deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable) deriving (Eq, Foldable, Functor, Generic, Generic1, Mergeable, Ord, Show, Traversable)

View File

@ -51,6 +51,7 @@ categoriesForLanguage language name = case (language, name) of
(JavaScript, "class") -> Class (JavaScript, "class") -> Class
(JavaScript, "catch") -> Catch (JavaScript, "catch") -> Catch
(JavaScript, "finally") -> Finally (JavaScript, "finally") -> Finally
(JavaScript, "if_statement") -> If
(Ruby, "hash") -> Object (Ruby, "hash") -> Object
_ -> defaultCategoryForNodeName name _ -> defaultCategoryForNodeName name