1
1
mirror of https://github.com/github/semantic.git synced 2024-12-01 09:15:01 +03:00

Update toElseIf so we don't drop the elseClause for non If syntax clauses

This commit is contained in:
Rick Winfrey 2016-10-13 16:33:57 -05:00
parent a80cb67b89
commit 59a2531889

View File

@ -3,11 +3,10 @@ module Language.JavaScript where
import Data.Record import Data.Record
import Info import Info
import Prologue hiding (head) import Prologue
import Source import Source
import qualified Syntax as S import qualified Syntax as S
import Term import Term
import Data.List (head)
operators :: [Text] operators :: [Text]
operators = [ "op", "bool_op", "math_op", "delete_op", "type_op", "void_op", "rel_op", "bitwise_op" ] operators = [ "op", "bool_op", "math_op", "delete_op", "type_op", "void_op", "rel_op", "bitwise_op" ]
@ -50,9 +49,7 @@ termConstructor source sourceSpan name range children
("case", [ expr, body ]) -> S.Case expr body ("case", [ expr, body ]) -> S.Case expr body
("object", _) -> S.Object $ foldMap toTuple children ("object", _) -> S.Object $ foldMap toTuple children
("pair", _) -> S.Fixed children ("pair", _) -> S.Fixed children
("if_statement", [ expr, thenClause, elseClause ]) -> case unwrap elseClause of ("if_statement", [ expr, thenClause, elseClause ]) -> toElseIf expr thenClause elseClause
S.If{} -> S.If expr thenClause [(toElseIf elseClause)]
_ -> S.If expr thenClause [elseClause]
("if_statement", [ expr, thenClause ]) -> S.If expr thenClause [] ("if_statement", [ expr, thenClause ]) -> S.If expr thenClause []
("while_statement", [ expr, body ]) -> S.While expr body ("while_statement", [ expr, body ]) -> S.While expr body
("do_statement", [ expr, body ]) -> S.DoWhile expr body ("do_statement", [ expr, body ]) -> S.DoWhile expr body
@ -161,10 +158,16 @@ toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl chil
-- | Convert a If Term to If Syntax. This handles nested else-if clauses recursively, -- | Convert a If Term to If Syntax. This handles nested else-if clauses recursively,
-- | and satisfies arbitrarily long else-if clauses. -- | and satisfies arbitrarily long else-if clauses.
toElseIf :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields) toElseIf :: Term (S.Syntax Text) (Record fields)
toElseIf child = case unwrap child of -> Term (S.Syntax Text) (Record fields)
S.If expr thenClause elseClause -> cofree $ setCategory (extract child) If :< S.If expr thenClause (toElseIf <$> elseClause) -> Term (S.Syntax Text) (Record fields)
_ -> child -> S.Syntax Text (Term (S.Syntax Text) (Record fields))
toElseIf expr thenClause elseClause = S.If expr thenClause (elseClause' elseClause)
where
elseClause' term = case unwrap term of
S.If _ _ [] -> [ term ]
S.If then' else' children -> [ cofree (extract term :< S.If then' else' []) ] <> (elseClause' =<< children)
_ -> [ term ]
toTuple :: Term (S.Syntax Text) (Record fields) -> [Term (S.Syntax Text) (Record fields)] toTuple :: Term (S.Syntax Text) (Record fields) -> [Term (S.Syntax Text) (Record fields)]
toTuple child | S.Indexed [key,value] <- unwrap child = [cofree (extract child :< S.Pair key value)] toTuple child | S.Indexed [key,value] <- unwrap child = [cofree (extract child :< S.Pair key value)]