module Language.JavaScript.Parser.AST
( JSExpression (..)
, JSAnnot (..)
, JSBinOp (..)
, JSUnaryOp (..)
, JSSemi (..)
, JSAssignOp (..)
, JSTryCatch (..)
, JSTryFinally (..)
, JSStatement (..)
, JSBlock (..)
, JSSwitchParts (..)
, JSAST (..)
, JSObjectProperty (..)
, JSPropertyName (..)
, JSObjectPropertyList
, JSAccessor (..)
, JSIdent (..)
, JSVarInitializer (..)
, JSArrayElement (..)
, JSCommaList (..)
, JSCommaTrailingList (..)
, binOpEq
, showStripped
) where
import Data.Data
import Data.List
import Language.JavaScript.Parser.SrcLocation (TokenPosn (..))
import Language.JavaScript.Parser.Token
data JSAnnot
= JSAnnot !TokenPosn ![CommentAnnotation]
| JSAnnotSpace
| JSNoAnnot
deriving (Data, Eq, Show, Typeable)
data JSAST
= JSAstProgram ![JSStatement] !JSAnnot
| JSAstStatement !JSStatement !JSAnnot
| JSAstExpression !JSExpression !JSAnnot
| JSAstLiteral !JSExpression !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSStatement
= JSStatementBlock !JSAnnot ![JSStatement] !JSAnnot !JSSemi
| JSBreak !JSAnnot !JSIdent !JSSemi
| JSConstant !JSAnnot !(JSCommaList JSExpression) !JSSemi
| JSContinue !JSAnnot !JSIdent !JSSemi
| JSDoWhile !JSAnnot !JSStatement !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSSemi
| JSFor !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement
| JSForIn !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement
| JSForVar !JSAnnot !JSAnnot !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSStatement
| JSForVarIn !JSAnnot !JSAnnot !JSAnnot !JSExpression !JSBinOp !JSExpression !JSAnnot !JSStatement
| JSFunction !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSBlock !JSSemi
| JSIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement
| JSIfElse !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSAnnot !JSStatement
| JSLabelled !JSIdent !JSAnnot !JSStatement
| JSEmptyStatement !JSAnnot
| JSExpressionStatement !JSExpression !JSSemi
| JSAssignStatement !JSExpression !JSAssignOp !JSExpression !JSSemi
| JSMethodCall !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot !JSSemi
| JSReturn !JSAnnot !(Maybe JSExpression) !JSSemi
| JSSwitch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSAnnot ![JSSwitchParts] !JSAnnot !JSSemi
| JSThrow !JSAnnot !JSExpression !JSSemi
| JSTry !JSAnnot !JSBlock ![JSTryCatch] !JSTryFinally
| JSVariable !JSAnnot !(JSCommaList JSExpression) !JSSemi
| JSWhile !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement
| JSWith !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSStatement !JSSemi
deriving (Data, Eq, Show, Typeable)
data JSExpression
= JSIdentifier !JSAnnot !String
| JSDecimal !JSAnnot !String
| JSLiteral !JSAnnot !String
| JSHexInteger !JSAnnot !String
| JSOctal !JSAnnot !String
| JSStringLiteral !JSAnnot !String
| JSRegEx !JSAnnot !String
| JSArrayLiteral !JSAnnot ![JSArrayElement] !JSAnnot
| JSAssignExpression !JSExpression !JSAssignOp !JSExpression
| JSCallExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
| JSCallExpressionDot !JSExpression !JSAnnot !JSExpression
| JSCallExpressionSquare !JSExpression !JSAnnot !JSExpression !JSAnnot
| JSCommaExpression !JSExpression !JSAnnot !JSExpression
| JSExpressionBinary !JSExpression !JSBinOp !JSExpression
| JSExpressionParen !JSAnnot !JSExpression !JSAnnot
| JSExpressionPostfix !JSExpression !JSUnaryOp
| JSExpressionTernary !JSExpression !JSAnnot !JSExpression !JSAnnot !JSExpression
| JSFunctionExpression !JSAnnot !JSIdent !JSAnnot !(JSCommaList JSIdent) !JSAnnot !JSBlock
| JSMemberDot !JSExpression !JSAnnot !JSExpression
| JSMemberExpression !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
| JSMemberNew !JSAnnot !JSExpression !JSAnnot !(JSCommaList JSExpression) !JSAnnot
| JSMemberSquare !JSExpression !JSAnnot !JSExpression !JSAnnot
| JSNewExpression !JSAnnot !JSExpression
| JSObjectLiteral !JSAnnot !JSObjectPropertyList !JSAnnot
| JSUnaryExpression !JSUnaryOp !JSExpression
| JSVarInitExpression !JSExpression !JSVarInitializer
deriving (Data, Eq, Show, Typeable)
data JSBinOp
= JSBinOpAnd !JSAnnot
| JSBinOpBitAnd !JSAnnot
| JSBinOpBitOr !JSAnnot
| JSBinOpBitXor !JSAnnot
| JSBinOpDivide !JSAnnot
| JSBinOpEq !JSAnnot
| JSBinOpGe !JSAnnot
| JSBinOpGt !JSAnnot
| JSBinOpIn !JSAnnot
| JSBinOpInstanceOf !JSAnnot
| JSBinOpLe !JSAnnot
| JSBinOpLsh !JSAnnot
| JSBinOpLt !JSAnnot
| JSBinOpMinus !JSAnnot
| JSBinOpMod !JSAnnot
| JSBinOpNeq !JSAnnot
| JSBinOpOr !JSAnnot
| JSBinOpPlus !JSAnnot
| JSBinOpRsh !JSAnnot
| JSBinOpStrictEq !JSAnnot
| JSBinOpStrictNeq !JSAnnot
| JSBinOpTimes !JSAnnot
| JSBinOpUrsh !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSUnaryOp
= JSUnaryOpDecr !JSAnnot
| JSUnaryOpDelete !JSAnnot
| JSUnaryOpIncr !JSAnnot
| JSUnaryOpMinus !JSAnnot
| JSUnaryOpNot !JSAnnot
| JSUnaryOpPlus !JSAnnot
| JSUnaryOpTilde !JSAnnot
| JSUnaryOpTypeof !JSAnnot
| JSUnaryOpVoid !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSSemi
= JSSemi !JSAnnot
| JSSemiAuto
deriving (Data, Eq, Show, Typeable)
data JSAssignOp
= JSAssign !JSAnnot
| JSTimesAssign !JSAnnot
| JSDivideAssign !JSAnnot
| JSModAssign !JSAnnot
| JSPlusAssign !JSAnnot
| JSMinusAssign !JSAnnot
| JSLshAssign !JSAnnot
| JSRshAssign !JSAnnot
| JSUrshAssign !JSAnnot
| JSBwAndAssign !JSAnnot
| JSBwXorAssign !JSAnnot
| JSBwOrAssign !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSTryCatch
= JSCatch !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSBlock
| JSCatchIf !JSAnnot !JSAnnot !JSExpression !JSAnnot !JSExpression !JSAnnot !JSBlock
deriving (Data, Eq, Show, Typeable)
data JSTryFinally
= JSFinally !JSAnnot !JSBlock
| JSNoFinally
deriving (Data, Eq, Show, Typeable)
data JSBlock
= JSBlock !JSAnnot ![JSStatement] !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSSwitchParts
= JSCase !JSAnnot !JSExpression !JSAnnot ![JSStatement]
| JSDefault !JSAnnot !JSAnnot ![JSStatement]
deriving (Data, Eq, Show, Typeable)
data JSVarInitializer
= JSVarInit !JSAnnot !JSExpression
| JSVarInitNone
deriving (Data, Eq, Show, Typeable)
data JSObjectProperty
= JSPropertyAccessor !JSAccessor !JSPropertyName !JSAnnot ![JSExpression] !JSAnnot !JSBlock
| JSPropertyNameandValue !JSPropertyName !JSAnnot ![JSExpression]
deriving (Data, Eq, Show, Typeable)
data JSPropertyName
= JSPropertyIdent !JSAnnot !String
| JSPropertyString !JSAnnot !String
| JSPropertyNumber !JSAnnot !String
deriving (Data, Eq, Show, Typeable)
type JSObjectPropertyList = JSCommaTrailingList JSObjectProperty
data JSAccessor
= JSAccessorGet !JSAnnot
| JSAccessorSet !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSIdent
= JSIdentName !JSAnnot !String
| JSIdentNone
deriving (Data, Eq, Show, Typeable)
data JSArrayElement
= JSArrayElement !JSExpression
| JSArrayComma !JSAnnot
deriving (Data, Eq, Show, Typeable)
data JSCommaList a
= JSLCons !(JSCommaList a) !JSAnnot !a
| JSLOne !a
| JSLNil
deriving (Data, Eq, Show, Typeable)
data JSCommaTrailingList a
= JSCTLComma !(JSCommaList a) !JSAnnot
| JSCTLNone !(JSCommaList a)
deriving (Data, Eq, Show, Typeable)
showStripped :: JSAST -> String
showStripped (JSAstProgram xs _) = "JSAstProgram " ++ ss xs
showStripped (JSAstStatement s _) = "JSAstStatement (" ++ ss s ++ ")"
showStripped (JSAstExpression e _) = "JSAstExpression (" ++ ss e ++ ")"
showStripped (JSAstLiteral s _) = "JSAstLiteral (" ++ ss s ++ ")"
class ShowStripped a where
ss :: a -> String
instance ShowStripped JSStatement where
ss (JSStatementBlock _ xs _ _) = "JSStatementBlock " ++ ss xs
ss (JSBreak _ JSIdentNone s) = "JSBreak" ++ commaIf (ss s)
ss (JSBreak _ (JSIdentName _ n) s) = "JSBreak " ++ singleQuote n ++ commaIf (ss s)
ss (JSContinue _ JSIdentNone s) = "JSContinue" ++ commaIf (ss s)
ss (JSContinue _ (JSIdentName _ n) s) = "JSContinue " ++ singleQuote n ++ commaIf (ss s)
ss (JSConstant _ xs _as) = "JSConstant " ++ ss xs
ss (JSDoWhile _d x1 _w _lb x2 _rb x3) = "JSDoWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
ss (JSFor _ _lb x1s _s1 x2s _s2 x3s _rb x4) = "JSFor " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
ss (JSForIn _ _lb x1s _i x2 _rb x3) = "JSForIn " ++ ss x1s ++ " (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
ss (JSForVar _ _lb _v x1s _s1 x2s _s2 x3s _rb x4) = "JSForVar " ++ ss x1s ++ " " ++ ss x2s ++ " " ++ ss x3s ++ " (" ++ ss x4 ++ ")"
ss (JSForVarIn _ _lb _v x1 _i x2 _rb x3) = "JSForVarIn (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
ss (JSFunction _ n _lb pl _rb x3 _) = "JSFunction " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ ")"
ss (JSIf _ _lb x1 _rb x2) = "JSIf (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
ss (JSIfElse _ _lb x1 _rb x2 _e x3) = "JSIfElse (" ++ ss x1 ++ ") (" ++ ss x2 ++ ") (" ++ ss x3 ++ ")"
ss (JSLabelled x1 _c x2) = "JSLabelled (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
ss (JSEmptyStatement _) = "JSEmptyStatement"
ss (JSExpressionStatement l s) = ss l ++ (let x = ss s in if not (null x) then ',':x else "")
ss (JSAssignStatement lhs op rhs s) ="JSOpAssign (" ++ ss op ++ "," ++ ss lhs ++ "," ++ ss rhs ++ (let x = ss s in if not (null x) then "),"++x else ")")
ss (JSMethodCall e _ a _ s) = "JSMethodCall (" ++ ss e ++ ",JSArguments " ++ ss a ++ (let x = ss s in if not (null x) then "),"++x else ")")
ss (JSReturn _ (Just me) s) = "JSReturn " ++ ss me ++ " " ++ ss s
ss (JSReturn _ Nothing s) = "JSReturn " ++ ss s
ss (JSSwitch _ _lp x _rp _lb x2 _rb _) = "JSSwitch (" ++ ss x ++ ") " ++ ss x2
ss (JSThrow _ x _) = "JSThrow (" ++ ss x ++ ")"
ss (JSTry _ xt1 xtc xtf) = "JSTry (" ++ ss xt1 ++ "," ++ ss xtc ++ "," ++ ss xtf ++ ")"
ss (JSVariable _ xs _as) = "JSVariable " ++ ss xs
ss (JSWhile _ _lb x1 _rb x2) = "JSWhile (" ++ ss x1 ++ ") (" ++ ss x2 ++ ")"
ss (JSWith _ _lb x1 _rb x _) = "JSWith (" ++ ss x1 ++ ") (" ++ ss x ++ ")"
instance ShowStripped JSExpression where
ss (JSArrayLiteral _lb xs _rb) = "JSArrayLiteral " ++ ss xs
ss (JSAssignExpression lhs op rhs) = "JSOpAssign (" ++ ss op ++ "," ++ ss lhs ++ "," ++ ss rhs ++ ")"
ss (JSCallExpression ex _ xs _) = "JSCallExpression ("++ ss ex ++ ",JSArguments " ++ ss xs ++ ")"
ss (JSCallExpressionDot ex _os xs) = "JSCallExpressionDot (" ++ ss ex ++ "," ++ ss xs ++ ")"
ss (JSCallExpressionSquare ex _os xs _cs) = "JSCallExpressionSquare (" ++ ss ex ++ "," ++ ss xs ++ ")"
ss (JSDecimal _ s) = "JSDecimal " ++ singleQuote s
ss (JSCommaExpression l _ r) = "JSExpression [" ++ ss l ++ "," ++ ss r ++ "]"
ss (JSExpressionBinary x2 op x3) = "JSExpressionBinary (" ++ ss op ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
ss (JSExpressionParen _lp x _rp) = "JSExpressionParen (" ++ ss x ++ ")"
ss (JSExpressionPostfix xs op) = "JSExpressionPostfix (" ++ ss op ++ "," ++ ss xs ++ ")"
ss (JSExpressionTernary x1 _q x2 _c x3) = "JSExpressionTernary (" ++ ss x1 ++ "," ++ ss x2 ++ "," ++ ss x3 ++ ")"
ss (JSFunctionExpression _ n _lb pl _rb x3) = "JSFunctionExpression " ++ ssid n ++ " " ++ ss pl ++ " (" ++ ss x3 ++ "))"
ss (JSHexInteger _ s) = "JSHexInteger " ++ singleQuote s
ss (JSOctal _ s) = "JSOctal " ++ singleQuote s
ss (JSIdentifier _ s) = "JSIdentifier " ++ singleQuote s
ss (JSLiteral _ []) = "JSLiteral ''"
ss (JSLiteral _ s) = "JSLiteral " ++ singleQuote s
ss (JSMemberDot x1s _d x2 ) = "JSMemberDot (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
ss (JSMemberExpression e _ a _) = "JSMemberExpression (" ++ ss e ++ ",JSArguments " ++ ss a ++ ")"
ss (JSMemberNew _a n _ s _) = "JSMemberNew (" ++ ss n ++ ",JSArguments " ++ ss s ++ ")"
ss (JSMemberSquare x1s _lb x2 _rb) = "JSMemberSquare (" ++ ss x1s ++ "," ++ ss x2 ++ ")"
ss (JSNewExpression _n e) = "JSNewExpression " ++ ss e
ss (JSObjectLiteral _lb xs _rb) = "JSObjectLiteral " ++ ss xs
ss (JSRegEx _ s) = "JSRegEx " ++ singleQuote s
ss (JSStringLiteral _ s) = "JSStringLiteral " ++ s
ss (JSUnaryExpression op x) = "JSUnaryExpression (" ++ ss op ++ "," ++ ss x ++ ")"
ss (JSVarInitExpression x1 x2) = "JSVarInitExpression (" ++ ss x1 ++ ") " ++ ss x2
instance ShowStripped JSTryCatch where
ss (JSCatch _ _lb x1 _rb x3) = "JSCatch (" ++ ss x1 ++ "," ++ ss x3 ++ ")"
ss (JSCatchIf _ _lb x1 _ ex _rb x3) = "JSCatch (" ++ ss x1 ++ ") if " ++ ss ex ++ " (" ++ ss x3 ++ ")"
instance ShowStripped JSTryFinally where
ss (JSFinally _ x) = "JSFinally (" ++ ss x ++ ")"
ss JSNoFinally = "JSFinally ()"
instance ShowStripped JSIdent where
ss (JSIdentName _ s) = "JSIdentifier " ++ singleQuote s
ss JSIdentNone = "JSIdentNone"
instance ShowStripped JSObjectProperty where
ss (JSPropertyNameandValue x1 _colon x2s) = "JSPropertyNameandValue (" ++ ss x1 ++ ") " ++ ss x2s
ss (JSPropertyAccessor s x1 _lb1 x2s _rb1 x3) = "JSPropertyAccessor " ++ ss s ++ " (" ++ ss x1 ++ ") " ++ ss x2s ++ " (" ++ ss x3 ++ ")"
instance ShowStripped JSPropertyName where
ss (JSPropertyIdent _ s) = "JSIdentifier " ++ singleQuote s
ss (JSPropertyString _ s) = "JSIdentifier " ++ singleQuote s
ss (JSPropertyNumber _ s) = "JSIdentifier " ++ singleQuote s
instance ShowStripped JSAccessor where
ss (JSAccessorGet _) = "JSAccessorGet"
ss (JSAccessorSet _) = "JSAccessorSet"
instance ShowStripped JSBlock where
ss (JSBlock _ xs _) = "JSBlock " ++ ss xs
instance ShowStripped JSSwitchParts where
ss (JSCase _ x1 _c x2s) = "JSCase (" ++ ss x1 ++ ") (" ++ ss x2s ++ ")"
ss (JSDefault _ _c xs) = "JSDefault (" ++ ss xs ++ ")"
instance ShowStripped JSBinOp where
ss (JSBinOpAnd _) = "'&&'"
ss (JSBinOpBitAnd _) = "'&'"
ss (JSBinOpBitOr _) = "'|'"
ss (JSBinOpBitXor _) = "'^'"
ss (JSBinOpDivide _) = "'/'"
ss (JSBinOpEq _) = "'=='"
ss (JSBinOpGe _) = "'>='"
ss (JSBinOpGt _) = "'>'"
ss (JSBinOpIn _) = "'in'"
ss (JSBinOpInstanceOf _) = "'instanceof'"
ss (JSBinOpLe _) = "'<='"
ss (JSBinOpLsh _) = "'<<'"
ss (JSBinOpLt _) = "'<'"
ss (JSBinOpMinus _) = "'-'"
ss (JSBinOpMod _) = "'%'"
ss (JSBinOpNeq _) = "'!='"
ss (JSBinOpOr _) = "'||'"
ss (JSBinOpPlus _) = "'+'"
ss (JSBinOpRsh _) = "'>>'"
ss (JSBinOpStrictEq _) = "'==='"
ss (JSBinOpStrictNeq _) = "'!=='"
ss (JSBinOpTimes _) = "'*'"
ss (JSBinOpUrsh _) = "'>>>'"
instance ShowStripped JSUnaryOp where
ss (JSUnaryOpDecr _) = "'--'"
ss (JSUnaryOpDelete _) = "'delete'"
ss (JSUnaryOpIncr _) = "'++'"
ss (JSUnaryOpMinus _) = "'-'"
ss (JSUnaryOpNot _) = "'!'"
ss (JSUnaryOpPlus _) = "'+'"
ss (JSUnaryOpTilde _) = "'~'"
ss (JSUnaryOpTypeof _) = "'typeof'"
ss (JSUnaryOpVoid _) = "'void'"
instance ShowStripped JSAssignOp where
ss (JSAssign _) = "'='"
ss (JSTimesAssign _) = "'*='"
ss (JSDivideAssign _) = "'/='"
ss (JSModAssign _) = "'%='"
ss (JSPlusAssign _) = "'+='"
ss (JSMinusAssign _) = "'-='"
ss (JSLshAssign _) = "'<<='"
ss (JSRshAssign _) = "'>>='"
ss (JSUrshAssign _) = "'>>>='"
ss (JSBwAndAssign _) = "'&='"
ss (JSBwXorAssign _) = "'^='"
ss (JSBwOrAssign _) = "'|='"
instance ShowStripped JSVarInitializer where
ss (JSVarInit _ n) = "[" ++ ss n ++ "]"
ss JSVarInitNone = ""
instance ShowStripped JSSemi where
ss (JSSemi _) = "JSSemicolon"
ss JSSemiAuto = ""
instance ShowStripped JSArrayElement where
ss (JSArrayElement e) = ss e
ss (JSArrayComma _) = "JSComma"
instance ShowStripped a => ShowStripped (JSCommaList a) where
ss xs = "(" ++ commaJoin (map ss $ fromCommaList xs) ++ ")"
instance ShowStripped a => ShowStripped (JSCommaTrailingList a) where
ss (JSCTLComma xs _) = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ ",JSComma]"
ss (JSCTLNone xs) = "[" ++ commaJoin (map ss $ fromCommaList xs) ++ "]"
instance ShowStripped a => ShowStripped [a] where
ss xs = "[" ++ commaJoin (map ss xs) ++ "]"
commaJoin :: [String] -> String
commaJoin s = intercalate "," $ filter (not . null) s
fromCommaList :: JSCommaList a -> [a]
fromCommaList (JSLCons l _ i) = fromCommaList l ++ [i]
fromCommaList (JSLOne i) = [i]
fromCommaList JSLNil = []
singleQuote :: String -> String
singleQuote s = '\'' : (s ++ "'")
ssid :: JSIdent -> String
ssid (JSIdentName _ s) = singleQuote s
ssid JSIdentNone = "''"
commaIf :: String -> String
commaIf "" = ""
commaIf xs = ',' : xs
deAnnot :: JSBinOp -> JSBinOp
deAnnot (JSBinOpAnd _) = JSBinOpAnd JSNoAnnot
deAnnot (JSBinOpBitAnd _) = JSBinOpBitAnd JSNoAnnot
deAnnot (JSBinOpBitOr _) = JSBinOpBitOr JSNoAnnot
deAnnot (JSBinOpBitXor _) = JSBinOpBitXor JSNoAnnot
deAnnot (JSBinOpDivide _) = JSBinOpDivide JSNoAnnot
deAnnot (JSBinOpEq _) = JSBinOpEq JSNoAnnot
deAnnot (JSBinOpGe _) = JSBinOpGe JSNoAnnot
deAnnot (JSBinOpGt _) = JSBinOpGt JSNoAnnot
deAnnot (JSBinOpIn _) = JSBinOpIn JSNoAnnot
deAnnot (JSBinOpInstanceOf _) = JSBinOpInstanceOf JSNoAnnot
deAnnot (JSBinOpLe _) = JSBinOpLe JSNoAnnot
deAnnot (JSBinOpLsh _) = JSBinOpLsh JSNoAnnot
deAnnot (JSBinOpLt _) = JSBinOpLt JSNoAnnot
deAnnot (JSBinOpMinus _) = JSBinOpMinus JSNoAnnot
deAnnot (JSBinOpMod _) = JSBinOpMod JSNoAnnot
deAnnot (JSBinOpNeq _) = JSBinOpNeq JSNoAnnot
deAnnot (JSBinOpOr _) = JSBinOpOr JSNoAnnot
deAnnot (JSBinOpPlus _) = JSBinOpPlus JSNoAnnot
deAnnot (JSBinOpRsh _) = JSBinOpRsh JSNoAnnot
deAnnot (JSBinOpStrictEq _) = JSBinOpStrictEq JSNoAnnot
deAnnot (JSBinOpStrictNeq _) = JSBinOpStrictNeq JSNoAnnot
deAnnot (JSBinOpTimes _) = JSBinOpTimes JSNoAnnot
deAnnot (JSBinOpUrsh _) = JSBinOpUrsh JSNoAnnot
binOpEq :: JSBinOp -> JSBinOp -> Bool
binOpEq a b = deAnnot a == deAnnot b