diff options
author | AndreyChudnov <> | 2012-10-30 21:31:34 (GMT) |
---|---|---|
committer | hdiff <hdiff@luite.com> | 2012-10-30 21:31:34 (GMT) |
commit | de9b6e7462e03e80e3b048a621677c4f6723137f (patch) | |
tree | 2fc30dafc19d429e6c93f0c53e463056db279e1b | |
parent | dd7d66ebb5eac482b20b4e9b7e2e72e4264f85b6 (diff) |
version 0.100.10
-rw-r--r-- | CHANGELOG | 9 | ||||
-rw-r--r-- | language-ecmascript.cabal | 33 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Analysis/Environment.hs | 9 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Analysis/LabelSets.hs | 4 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Parser.hs | 56 | ||||
-rw-r--r-- | src/Language/ECMAScript3/PrettyPrint.hs | 319 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Syntax.hs | 12 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Syntax/Annotations.hs | 1 | ||||
-rw-r--r-- | src/Language/ECMAScript3/Syntax/Arbitrary.hs | 383 | ||||
-rw-r--r-- | src/PrettyTest.hs | 30 | ||||
-rw-r--r-- | src/UnitTest.hs | 2 | ||||
-rw-r--r-- | tests/parse-pretty/flapjax-fxinternal-22dec2008.js | 930 |
12 files changed, 1197 insertions, 591 deletions
@@ -1,5 +1,14 @@ Version change log. +=0.10= + +The ParenExpr constructor was removed from the Expression AST +(WARNING: might break some builds). The pretty printer was rewritten +to automatically parenthesize sub-expressions based on operator +precedence. Added a (beta quality) arbitrary instance for all the +AST's to generate random JavaScript programs (useful for testing). + + =0.9.1= Increased the upper bound on data-default in dependencies. See https://github.com/jswebtools/language-ecmascript/pull/5 diff --git a/language-ecmascript.cabal b/language-ecmascript.cabal index 09ca7c6..5ab4d60 100644 --- a/language-ecmascript.cabal +++ b/language-ecmascript.cabal @@ -1,5 +1,5 @@ Name: language-ecmascript -Version: 0.9.1 +Version: 0.10 Cabal-Version: >= 1.10 Copyright: (c) 2007-2012 Brown University, (c) 2008-2010 Claudiu Saftoiu, (c) 2012 Stevens Institute of Technology @@ -30,7 +30,7 @@ Source-repository head Source-repository this type: git location: git://github.com/jswebtools/language-ecmascript.git - tag: 0.9 + tag: 0.9.1 Library Hs-Source-Dirs: @@ -43,7 +43,8 @@ Library containers >= 0.1, syb >= 0.1, uniplate >= 1.6 && <1.7, - data-default >= 0.4 && <0.6 + data-default >= 0.4 && <0.6, + QuickCheck >= 2.4.1.1 ghc-options: -fwarn-incomplete-patterns Exposed-Modules: @@ -53,6 +54,7 @@ Library Language.ECMAScript3.PrettyPrint Language.ECMAScript3.Syntax Language.ECMAScript3.Syntax.Annotations + Language.ECMAScript3.Syntax.Arbitrary Language.ECMAScript3.Analysis.Environment Language.ECMAScript3.Analysis.LabelSets Default-Extensions: @@ -73,7 +75,30 @@ Test-Suite unittest directory, filepath, HUnit, - data-default >=0.4 && <0.6 + data-default >=0.4 && <0.6, + QuickCheck >= 2.4.1.1 + Default-Extensions: DeriveDataTypeable, ScopedTypeVariables, DeriveFunctor, DeriveFoldable, DeriveTraversable, FlexibleContexts + Default-Language: Haskell2010 + ghc-options: + -fwarn-incomplete-patterns + +Test-Suite prettytest + Hs-Source-Dirs: src + Type: exitcode-stdio-1.0 + Main-Is: PrettyTest.hs + Build-Depends: + base >= 4 && < 5, + mtl >= 1.1.0.1, + parsec < 3.2.0, + pretty >= 0.1, + containers >= 0.1, + syb >= 0.1, + directory, + filepath, + HUnit, + data-default >=0.4 && <0.5, + QuickCheck >= 2.4.1.1, + uniplate >= 1.6 && <1.7 Default-Extensions: DeriveDataTypeable, ScopedTypeVariables, DeriveFunctor, DeriveFoldable, DeriveTraversable, FlexibleContexts Default-Language: Haskell2010 ghc-options: diff --git a/src/Language/ECMAScript3/Analysis/Environment.hs b/src/Language/ECMAScript3/Analysis/Environment.hs index c845203..13b51f2 100644 --- a/src/Language/ECMAScript3/Analysis/Environment.hs +++ b/src/Language/ECMAScript3/Analysis/Environment.hs @@ -72,10 +72,10 @@ expr e = case e of CondExpr _ e1 e2 e3 -> unions [expr e1, expr e2, expr e3] AssignExpr _ _ lv e -> unions [lvalue lv, expr e] UnaryAssignExpr _ _ lv -> lvalue lv - ParenExpr _ e -> expr e ListExpr _ es -> unions (map expr es) CallExpr _ e es -> unions [expr e, unions $ map expr es] - FuncExpr _ _ args s -> nest $ unions [unions $ map decl args, stmt s] + FuncExpr _ _ args ss -> nest $ unions [unions $ map decl args + ,unions $ map stmt ss] caseClause :: CaseClause SourcePos -> Partial caseClause cc = case cc of @@ -122,8 +122,9 @@ stmt s = case s of ReturnStmt _ me -> maybe empty expr me WithStmt _ e s -> unions [expr e, stmt s] VarDeclStmt _ decls -> unions $ map varDecl decls - FunctionStmt _ fnId args s -> - unions [decl fnId, nest $ unions [unions $ map decl args, stmt s]] + FunctionStmt _ fnId args ss -> + unions [decl fnId, nest $ unions [unions $ map decl args, + unions $ map stmt ss]] -- |The statically-determinate lexical structure of a JavaScript program. data EnvTree = EnvTree (M.Map String SourcePos) [EnvTree] diff --git a/src/Language/ECMAScript3/Analysis/LabelSets.hs b/src/Language/ECMAScript3/Analysis/LabelSets.hs index e8b75a9..9f99db1 100644 --- a/src/Language/ECMAScript3/Analysis/LabelSets.hs +++ b/src/Language/ECMAScript3/Analysis/LabelSets.hs @@ -41,7 +41,7 @@ annotateFuncStmtBodies :: Data a => -> Statement a annotateFuncStmtBodies r w s = case s of FunctionStmt a name params body -> - let newbody = descend (annotateStatement r w) body + let newbody = map (descend (annotateStatement r w)) body in FunctionStmt a name params newbody _ -> s @@ -52,7 +52,7 @@ annotateFuncExprBodies :: Data a => -> Expression a annotateFuncExprBodies r w e = case e of FuncExpr a mname params body -> - let newbody = descend (annotateStatement r w) body + let newbody = map (descend (annotateStatement r w)) body in FuncExpr a mname params newbody _ -> e diff --git a/src/Language/ECMAScript3/Parser.hs b/src/Language/ECMAScript3/Parser.hs index cebbf53..0dd1725 100644 --- a/src/Language/ECMAScript3/Parser.hs +++ b/src/Language/ECMAScript3/Parser.hs @@ -1,5 +1,5 @@ --- | Parser for ECMAScript 3. - + -- | Parser for ECMAScript 3. +{-# LANGUAGE FlexibleContexts #-} module Language.ECMAScript3.Parser (parse , parseScriptFromString @@ -15,6 +15,9 @@ module Language.ECMAScript3.Parser , StatementParser , ExpressionParser , assignExpr + -- debugging, remove the next 2 lines + , mkDecimal + , intLen ) where import Language.ECMAScript3.Lexer hiding (identifier) @@ -137,7 +140,7 @@ parseDoWhileStmt:: StatementParser parseDoWhileStmt = do pos <- getPosition reserved "do" - body <- parseBlockStmt + body <- parseStatement reserved "while" <?> "while at the end of a do block" test <- parseParenExpr <?> "parenthesized test-expression in do loop" optional semi @@ -294,7 +297,8 @@ parseFunctionStmt = do name <- try (reserved "function" >> identifier) -- ambiguity with FuncExpr args <- parens (identifier `sepBy` comma) -- label sets don't cross function boundaries - body <- withFreshLabelStack parseBlockStmt <?> "function body in { ... }" + BlockStmt _ body <- withFreshLabelStack parseBlockStmt <?> + "function body in { ... }" return (FunctionStmt pos name args body) parseStatement:: StatementParser @@ -359,7 +363,7 @@ parseFuncExpr = do name <- optionMaybe identifier args <- parens (identifier `sepBy` comma) -- labels don't cross function boundaries - body <- withFreshLabelStack parseBlockStmt + BlockStmt _ body <- withFreshLabelStack parseBlockStmt return $ FuncExpr pos name args body --{{{ parsing strings @@ -432,12 +436,13 @@ parseRegexpLit = do parseChar = noneOf "/" let parseRe = (char '/' >> return "") <|> (do char '\\' - ch <- anyChar -- TOOD: too lenient + ch <- anyChar -- TODO: too lenient rest <- parseRe return ('\\':ch:rest)) <|> liftM2 (:) anyChar parseRe pos <- getPosition char '/' + notFollowedBy $ char '/' pat <- parseRe --many1 parseChar flags <- parseFlags spaces -- crucial for Parsec.Token parsers @@ -467,11 +472,15 @@ hexLit = do [(hex,"")] <- return $ Numeric.readHex digits return (True, hex) --- Creates a decimal value from a whole, fractional and exponent part. -mkDecimal:: Double -> Double -> Int -> Double -mkDecimal w f e = if f >= 1.0 - then mkDecimal w (f / 10.0) e - else (w + f) * (10.0 ^^ e) +-- | Creates a decimal value from a whole, fractional and exponent part. +mkDecimal :: Integer -> Integer -> Integer -> Integer -> Double +mkDecimal whole frac fracLen exp = + ((fromInteger whole) + ((fromInteger frac) * (10 ^^ (-fracLen)))) * (10 ^^ exp) + +-- mkDecimal:: Double -> Double -> Int -> Double +-- mkDecimal w f e = if f >= 1.0 +-- then mkDecimal w (f / 10.0) e +-- else (w + f) * (10.0 ^^ e) exponentPart = do oneOf "eE" @@ -486,12 +495,18 @@ decLit = mexp <- option Nothing (jparser exponentPart) if isNothing mfrac && isNothing mexp then return (True, fromIntegral whole) - else return (False, mkDecimal (fromIntegral whole) - (fromIntegral (fromMaybe 0 mfrac)) - (fromIntegral (fromMaybe 0 mexp)))) <|> + else let frac = fromIntegral (fromMaybe 0 mfrac) + in return (False, mkDecimal (fromIntegral whole) frac + (intLen frac) + (fromIntegral (fromMaybe 0 mexp)))) + <|> (do frac <- char '.' >> decimal exp <- option 0 exponentPart - return (False, mkDecimal 0.0 (fromIntegral frac) (fromIntegral exp))) + let ifrac = fromIntegral frac + return (False, mkDecimal 0 ifrac (intLen frac) (fromIntegral exp))) + +intLen i | i `div` 10 < 1 = 1 +intLen i | otherwise = 1 + intLen (i `div` 10) parseNumLit:: ExpressionParser parseNumLit = do @@ -528,7 +543,7 @@ bracketRef e = brackets (withPos cstr parseExpression) <?> "[property-ref]" ------------------------------------------------------------------------------- parseParenExpr:: ExpressionParser -parseParenExpr = withPos ParenExpr (parens parseListExpr) +parseParenExpr = parens parseListExpr -- everything above expect functions parseExprForNew = parseThisRef <|> parseNullLit <|> parseBoolLit <|> parseStringLit @@ -720,7 +735,10 @@ assignExpr = do parseExpression:: ExpressionParser parseExpression = assignExpr -parseListExpr = liftM2 ListExpr getPosition (assignExpr `sepBy1` comma) +parseListExpr = assignExpr `sepBy1` comma >>= \exprs -> + case exprs of + [expr] -> return expr + es -> liftM2 ListExpr getPosition (return es) parseScript:: CharParser (JavaScript SourcePos) parseScript = do @@ -728,8 +746,8 @@ parseScript = do liftM2 Script getPosition (parseStatement `sepBy` whiteSpace) -- | Parse from a stream; same as 'Text.Parsec.parse' -parse :: Stream s Identity t => - Parsec s [String] a -- ^ The parser to use +parse :: Stream s Identity t + => Parsec s [String] a -- ^ The parser to use -> SourceName -- ^ Name of the source file -> s -- ^ the stream to parse, usually a 'String' -> Either ParseError a diff --git a/src/Language/ECMAScript3/PrettyPrint.hs b/src/Language/ECMAScript3/PrettyPrint.hs index b67b638..be82b6b 100644 --- a/src/Language/ECMAScript3/PrettyPrint.hs +++ b/src/Language/ECMAScript3/PrettyPrint.hs @@ -1,8 +1,6 @@ -- |Pretty-printing JavaScript. module Language.ECMAScript3.PrettyPrint ( --- stmt --- , expr javaScript , renderStatements , renderExpression @@ -10,6 +8,7 @@ module Language.ECMAScript3.PrettyPrint import Text.PrettyPrint.HughesPJ import Language.ECMAScript3.Syntax +import Prelude hiding (maybe) -- | Renders a list of statements as a 'String' renderStatements :: [Statement a] -> String @@ -17,69 +16,76 @@ renderStatements = render . stmtList -- | Renders a list of statements as a 'String' renderExpression :: Expression a -> String -renderExpression = render . expr +renderExpression = render . (ppExpression True) -- Displays the statement in { ... }, unless it is a block itself. inBlock:: Statement a -> Doc -inBlock s@(BlockStmt _ _) = stmt s -inBlock s = lbrace $+$ nest 2 (stmt s) $+$ rbrace +inBlock s@(BlockStmt _ _) = ppStatement s +inBlock s = asBlock [s] --- Displays the expression in ( ... ), unless it is a parenthesized expression -inParens:: Expression a -> Doc -inParens e@(ParenExpr _ _) = expr e -inParens e = parens (expr e) +asBlock :: [Statement a] -> Doc +asBlock ss = lbrace $+$ nest 2 (stmtList ss) $$ rbrace -pp (Id _ str) = text str +ppId (Id _ str) = text str forInit :: ForInit a -> Doc forInit t = case t of NoInit -> empty - VarInit vs -> text "var" <+> cat (punctuate comma $ map varDecl vs) - ExprInit e -> expr e + VarInit vs -> text "var" <+> cat (punctuate comma $ map (ppVarDecl False) vs) + ExprInit e -> ppExpression False e forInInit :: ForInInit a -> Doc forInInit t = case t of - ForInVar id -> text "var" <+> pp id - ForInLVal lv -> lvalue lv + ForInVar id -> text "var" <+> ppId id + ForInLVal lv -> ppLValue lv caseClause :: CaseClause a -> Doc caseClause (CaseClause _ e ss) = - text "case" $+$ expr e <+> colon $$ nest 2 (stmtList ss) + text "case" $+$ ppExpression True e <+> colon $$ nest 2 (stmtList ss) caseClause (CaseDefault _ ss) = text "default:" $$ nest 2 (stmtList ss) -varDecl :: VarDecl a -> Doc -varDecl (VarDecl _ id Nothing) = pp id -varDecl (VarDecl _ id (Just e)) = pp id <+> equals <+> expr e +ppVarDecl :: Bool -> VarDecl a -> Doc +ppVarDecl hasIn vd = case vd of + VarDecl _ id Nothing -> ppId id + VarDecl _ id (Just e) -> ppId id <+> equals <+> ppAssignmentExpression hasIn e -stmt :: Statement a -> Doc -stmt s = case s of - BlockStmt _ ss -> lbrace $+$ nest 2 (stmtList ss) $$ rbrace +ppStatement :: Statement a -> Doc +ppStatement s = case s of + BlockStmt _ ss -> asBlock ss EmptyStmt _ -> semi - ExprStmt _ e -> expr e <> semi - IfSingleStmt _ test cons -> text "if" <+> inParens test $$ stmt cons - IfStmt _ test cons alt -> - text "if" <+> inParens test $$ stmt cons $$ text "else" <+> stmt alt + ExprStmt _ e@(CallExpr _ (FuncExpr {}) _ ) -> + parens (ppExpression True e) <> semi + ExprStmt _ e -> ppExpression True e <> semi + IfSingleStmt _ test cons -> text "if" <+> + parens (ppExpression True test) $$ + ppStatement cons + IfStmt _ test cons alt -> text "if" <+> parens (ppExpression True test) $$ + ppStatement cons $$ text "else" <+> ppStatement alt SwitchStmt _ e cases -> - text "switch" <+> inParens e $$ + text "switch" <+> parens (ppExpression True e) $$ braces (nest 2 (vcat (map caseClause cases))) - WhileStmt _ test body -> text "while" <+> inParens test $$ stmt body + WhileStmt _ test body -> text "while" <+> parens (ppExpression True test) $$ + ppStatement body ReturnStmt _ Nothing -> text "return" - ReturnStmt _ (Just e) -> text "return" <+> expr e + ReturnStmt _ (Just e) -> text "return" <+> ppExpression True e DoWhileStmt _ s e -> - text "do" $$ (stmt s <+> text "while" <+> inParens e <> semi) + text "do" $$ + (ppStatement s <+> text "while" <+> parens (ppExpression True e) <> semi) BreakStmt _ Nothing -> text "break" <> semi - BreakStmt _ (Just label) -> text "break" <+> pp label <> semi + BreakStmt _ (Just label) -> text "break" <+> ppId label <> semi ContinueStmt _ Nothing -> text "continue" <> semi - ContinueStmt _ (Just label) -> text"continue" <+> pp label <> semi - LabelledStmt _ label s -> pp label <> colon $$ stmt s + ContinueStmt _ (Just label) -> text"continue" <+> ppId label <> semi + LabelledStmt _ label s -> ppId label <> colon $$ ppStatement s ForInStmt p init e body -> text "for" <+> - parens (forInInit init <+> text "in" <+> expr e) $+$ stmt body + parens (forInInit init <+> text "in" <+> ppExpression True e) $+$ + ppStatement body ForStmt _ init incr test body -> text "for" <+> - parens (forInit init <> semi <+> mexpr incr <> semi <+> mexpr test) $$ - stmt body + parens (forInit init <> semi <+> maybe incr (ppExpression True) <> + semi <+> maybe test (ppExpression True)) $$ + ppStatement body TryStmt _ stmt mcatch mfinally -> text "try" $$ inBlock stmt $$ ppCatch $$ ppFinally where ppFinally = case mfinally of @@ -88,22 +94,22 @@ stmt s = case s of ppCatch = case mcatch of Nothing -> empty Just (CatchClause _ id s) -> - text "catch" <+> (parens.pp) id <+> inBlock s - ThrowStmt _ e -> text "throw" <+> expr e <> semi - WithStmt _ expr s -> text "with" <+> inParens expr $$ stmt s + text "catch" <+> (parens.ppId) id <+> inBlock s + ThrowStmt _ e -> text "throw" <+> ppExpression True e <> semi + WithStmt _ e s -> text "with" <+> parens (ppExpression True e) $$ ppStatement s VarDeclStmt _ decls -> - text "var" <+> cat (punctuate comma (map varDecl decls)) <> semi - FunctionStmt _ name args s -> - text "function" <+> pp name <> - parens (cat $ punctuate comma (map pp args)) $$ - inBlock s + text "var" <+> cat (punctuate comma (map (ppVarDecl True) decls)) <> semi + FunctionStmt _ name args body -> + text "function" <+> ppId name <> + parens (cat $ punctuate comma (map ppId args)) $$ + asBlock body stmtList :: [Statement a] -> Doc -stmtList = vcat . map stmt +stmtList = vcat . map ppStatement prop :: Prop a -> Doc prop p = case p of - PropId _ id -> pp id + PropId _ id -> ppId id PropString _ str -> doubleQuotes (text (jsEscape str)) PropNum _ n -> text (show n) @@ -173,57 +179,186 @@ jsEscape (ch:chs) = sel ch ++ jsEscape chs where sel '\\' = "\\\\" sel x = [x] -- We don't have to do anything about \X, \x and \u escape sequences. + +regexpEscape :: String -> String +regexpEscape "" = "" +regexpEscape "\\" = "\\\\" +regexpEscape ('\\':c:rest) = '\\':c:(regexpEscape rest) +regexpEscape ('/':rest) = '\\':'/':regexpEscape rest +regexpEscape (c:rest) = c:regexpEscape rest -lvalue :: LValue a -> Doc -lvalue (LVar _ x) = text x -lvalue (LDot _ e x) = expr e <> text "." <> text x -lvalue (LBracket _ e1 e2) = expr e1 <> brackets (expr e2) - -expr :: Expression a -> Doc -expr e = case e of - StringLit _ str -> doubleQuotes (text (jsEscape str)) - RegexpLit _ re global ci -> - text "/" <> text re <> text "/" <> g <> i where - g = if global then text "g" else empty - i = if ci then text "i" else empty - NumLit _ n -> text (show n) +ppLValue :: LValue a -> Doc +ppLValue (LVar _ x) = text x +ppLValue (LDot _ e x) = ppMemberExpression e <> text "." <> text x +ppLValue (LBracket _ e1 e2) = ppMemberExpression e1 <> + brackets (ppExpression True e2) + +-- 11.1 +ppPrimaryExpression :: Expression a -> Doc +ppPrimaryExpression e = case e of + ThisRef _ -> text "this" + VarRef _ id -> ppId id + NullLit _ -> text "null" + BoolLit _ True -> text "true" + BoolLit _ False -> text "false" + NumLit _ n -> text (show n) IntLit _ n -> text (show n) - BoolLit _ True -> text "true" - BoolLit _ False -> text "false" - NullLit _ -> text "null" - ArrayLit _ es -> brackets $ cat $ punctuate comma (map expr es) + StringLit _ str -> doubleQuotes (text (jsEscape str)) + RegexpLit _ reg g ci -> text "/" <> (text (regexpEscape reg)) <> text "/" <> + (if g then text "g" else empty) <> + (if ci then text "i" else empty) + ArrayLit _ es -> + brackets $ cat $ punctuate comma (map (ppAssignmentExpression True) es) ObjectLit _ xs -> braces (hsep (punctuate comma (map pp' xs))) where - pp' (n,v) = prop n <> colon <+> expr v - ThisRef _ -> text "this" - VarRef _ id -> pp id - DotRef _ e' id -> expr e' <> text "." <> pp id - BracketRef _ container key -> expr container <> brackets (expr key) - NewExpr _ constr args -> - text "new" <+> expr constr <> - parens (cat $ punctuate comma (map expr args)) - PrefixExpr _ op e' -> prefixOp op <+> expr e' - InfixExpr _ op left right -> expr left <+> infixOp op <+> expr right - CondExpr _ test cons alt -> - expr test <+> text "?" <+> expr cons <+> colon <+> expr alt - AssignExpr _ op l r -> lvalue l <+> assignOp op <+> expr r - UnaryAssignExpr _ op e' -> case op of - PrefixInc -> text "++" <> lvalue e' - PrefixDec -> text "--" <> lvalue e' - PostfixInc -> lvalue e' <> text "++" - PostfixDec -> lvalue e' <> text "--" - ParenExpr _ e' -> parens (expr e') - ListExpr _ es -> cat $ punctuate comma (map expr es) - CallExpr _ f args -> - expr f <> parens (cat $ punctuate comma (map expr args)) - FuncExpr _ name args body -> - text "function" <+> text (maybe "" unId name) <+> - parens (cat $ punctuate comma (map pp args)) $$ - inBlock body - -mexpr :: Maybe (Expression a) -> Doc -mexpr Nothing = empty -mexpr (Just e) = expr e + pp' (n,v) = prop n <> colon <+> ppAssignmentExpression True v + _ -> parens $ ppExpression True e + +-- 11.2 +ppMemberExpression :: Expression a -> Doc +ppMemberExpression e = case e of + FuncExpr _ name params body -> + text "function" <+> maybe name ppId <+> + parens (cat $ punctuate comma (map ppId params)) $$ + asBlock body + DotRef _ obj id -> ppMemberExpression obj <> text "." <> ppId id + BracketRef _ obj key -> + ppMemberExpression obj <> brackets (ppExpression True key) + NewExpr _ ctor args -> + text "new" <+> ppMemberExpression ctor <> ppArguments args + _ -> ppPrimaryExpression e + +ppCallExpression :: Expression a -> Doc +ppCallExpression e = case e of + CallExpr _ f args -> ppCallExpression f <> ppArguments args + DotRef _ obj id -> ppCallExpression obj <> text "." <> ppId id + BracketRef _ obj key ->ppCallExpression obj <> brackets (ppExpression True key) + _ -> ppMemberExpression e + +ppArguments :: [Expression a] -> Doc +ppArguments es = + parens $ cat $ punctuate comma (map (ppAssignmentExpression True) es) + +ppLHSExpression :: Expression a -> Doc +ppLHSExpression = ppCallExpression + +-- 11.3 +ppPostfixExpression :: Expression a -> Doc +ppPostfixExpression e = case e of + UnaryAssignExpr _ PostfixInc e' -> ppLValue e' <> text "++" + UnaryAssignExpr _ PostfixDec e' -> ppLValue e' <> text "--" + _ -> ppLHSExpression e + +-- 11.4 +ppUnaryExpression :: Expression a -> Doc +ppUnaryExpression e = case e of + PrefixExpr _ op e' -> prefixOp op <+> ppUnaryExpression e' + UnaryAssignExpr _ PrefixInc e' -> text "++" <> ppLValue e' + UnaryAssignExpr _ PrefixDec e' -> text "--" <> ppLValue e' + _ -> ppPostfixExpression e + +-- 11.5 +ppMultiplicativeExpression :: Expression a -> Doc +ppMultiplicativeExpression e = case e of + InfixExpr _ op e1 e2 | op `elem` [OpMul, OpDiv, OpMod] -> + ppMultiplicativeExpression e1 <+> infixOp op <+> ppUnaryExpression e2 + _ -> ppUnaryExpression e + +-- 11.6 +ppAdditiveExpression :: Expression a -> Doc +ppAdditiveExpression e = case e of + InfixExpr _ op e1 e2 | op `elem` [OpAdd, OpSub] -> + ppAdditiveExpression e1 <+> infixOp op <+> ppMultiplicativeExpression e2 + _ -> ppMultiplicativeExpression e + +-- 11.7 +ppShiftExpression :: Expression a -> Doc +ppShiftExpression e = case e of + InfixExpr _ op e1 e2 | op `elem` [OpLShift, OpSpRShift, OpZfRShift] -> + ppShiftExpression e1 <+> infixOp op <+> ppAdditiveExpression e2 + _ -> ppAdditiveExpression e + +-- 11.8. +-- | @ppRelationalExpression True@ is RelationalExpression, +-- @ppRelationalExpression False@ is RelationalExpressionNoIn +ppRelationalExpression :: Bool -> Expression a -> Doc +ppRelationalExpression hasIn e = + let opsNoIn = [OpLT, OpGT, OpLEq, OpGEq, OpInstanceof] + ops = if hasIn then OpIn:opsNoIn else opsNoIn + in case e of + InfixExpr _ op e1 e2 | op `elem` ops -> + ppRelationalExpression hasIn e1 <+> infixOp op <+> ppShiftExpression e2 + _ -> ppShiftExpression e + +-- 11.9 +ppEqualityExpression :: Bool -> Expression a -> Doc +ppEqualityExpression hasIn e = case e of + InfixExpr _ op e1 e2 | op `elem` [OpEq, OpNEq, OpStrictEq, OpStrictNEq] -> + ppEqualityExpression hasIn e1 <+> infixOp op <+> + ppRelationalExpression hasIn e2 + _ -> ppRelationalExpression hasIn e + +-- 11.10 +ppBitwiseANDExpression :: Bool -> Expression a -> Doc +ppBitwiseANDExpression hasIn e = case e of + InfixExpr _ op@OpBAnd e1 e2 -> ppBitwiseANDExpression hasIn e1 <+> + infixOp op <+> + ppEqualityExpression hasIn e2 + _ -> ppEqualityExpression hasIn e + +ppBitwiseXORExpression :: Bool -> Expression a -> Doc +ppBitwiseXORExpression hasIn e = case e of + InfixExpr _ op@OpBXor e1 e2 -> ppBitwiseXORExpression hasIn e1 <+> + infixOp op <+> + ppBitwiseANDExpression hasIn e2 + _ -> ppBitwiseANDExpression hasIn e + +ppBitwiseORExpression :: Bool -> Expression a -> Doc +ppBitwiseORExpression hasIn e = case e of + InfixExpr _ op@OpBOr e1 e2 -> ppBitwiseORExpression hasIn e1 <+> + infixOp op <+> + ppBitwiseXORExpression hasIn e2 + _ -> ppBitwiseXORExpression hasIn e + +-- 11.11 +ppLogicalANDExpression :: Bool -> Expression a -> Doc +ppLogicalANDExpression hasIn e = case e of + InfixExpr _ op@OpLAnd e1 e2 -> ppLogicalANDExpression hasIn e1 <+> + infixOp op <+> + ppBitwiseORExpression hasIn e2 + _ -> ppBitwiseORExpression hasIn e + +ppLogicalORExpression :: Bool -> Expression a -> Doc +ppLogicalORExpression hasIn e = case e of + InfixExpr _ op@OpLOr e1 e2 -> ppLogicalORExpression hasIn e1 <+> + infixOp op <+> + ppLogicalANDExpression hasIn e2 + _ -> ppLogicalANDExpression hasIn e + +-- 11.12 +ppConditionalExpression :: Bool -> Expression a -> Doc +ppConditionalExpression hasIn e = case e of + CondExpr _ c et ee -> ppLogicalORExpression hasIn c <+> text "?" <+> + ppAssignmentExpression hasIn et <+> colon <+> + ppAssignmentExpression hasIn ee + _ -> ppLogicalORExpression hasIn e + +-- 11.13 +ppAssignmentExpression :: Bool -> Expression a -> Doc +ppAssignmentExpression hasIn e = case e of + AssignExpr _ op l r -> ppLValue l <+> assignOp op <+> + ppAssignmentExpression hasIn r + _ -> ppConditionalExpression hasIn e + +-- 11.14 +ppExpression :: Bool -> Expression a -> Doc +ppExpression hasIn e = case e of + ListExpr _ es -> cat $ punctuate comma (map (ppExpression hasIn) es) + _ -> ppAssignmentExpression hasIn e + +maybe :: Maybe a -> (a -> Doc) -> Doc +maybe Nothing _ = empty +maybe (Just a) f = f a -- | Renders a JavaScript program as a document, the show instance of -- 'Doc' will pretty-print it automatically diff --git a/src/Language/ECMAScript3/Syntax.hs b/src/Language/ECMAScript3/Syntax.hs index f43a33a..b5b2b13 100644 --- a/src/Language/ECMAScript3/Syntax.hs +++ b/src/Language/ECMAScript3/Syntax.hs @@ -1,4 +1,9 @@ --- |ECMAScript 3 syntax. /Spec/ refers to the ECMA-262 specification, 3rd edition. +-- |ECMAScript 3 syntax. /Spec/ refers to the ECMA-262 specification, +-- 3rd edition. +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE DeriveFoldable #-} module Language.ECMAScript3.Syntax (JavaScript(..) ,unJavaScript ,Statement(..) @@ -147,11 +152,10 @@ data Expression a -- ^ @e1 ? e2 : e3@, spec 11.12 | AssignExpr a AssignOp (LValue a) (Expression a) -- ^ @e1 \@=e2@, spec 11.13 - | ParenExpr a (Expression a) -- ^ @(e)@, spec 11.1.6 | ListExpr a [Expression a] -- ^ @e1, e2@, spec 11.14 | CallExpr a (Expression a) [Expression a] -- ^ @f(x,y,z)@, spec 11.2.3 --funcexprs are optionally named - | FuncExpr a (Maybe (Id a)) [Id a] (Statement a) + | FuncExpr a (Maybe (Id a)) [Id a] [Statement a] -- ^ @function f (x,y,z) {...}@, spec 11.2.5, 13 deriving (Show,Data,Typeable,Eq,Ord,Functor,Foldable,Traversable) @@ -220,7 +224,7 @@ data Statement a -- ^ @with (o) stmt@, spec 12.10 | VarDeclStmt a [VarDecl a] -- ^ @var x, y=42;@, spec 12.2 - | FunctionStmt a (Id a) {-name-} [Id a] {-args-} (Statement a) {-body-} + | FunctionStmt a (Id a) {-name-} [Id a] {-args-} [Statement a] {-body-} -- ^ @function f(x, y, z) {...}@, spec 13 deriving (Show,Data,Typeable,Eq,Ord,Functor,Foldable,Traversable) diff --git a/src/Language/ECMAScript3/Syntax/Annotations.hs b/src/Language/ECMAScript3/Syntax/Annotations.hs index a467319..bacc9b9 100644 --- a/src/Language/ECMAScript3/Syntax/Annotations.hs +++ b/src/Language/ECMAScript3/Syntax/Annotations.hs @@ -64,7 +64,6 @@ instance HasAnnotation Expression where (InfixExpr a op e1 e2) -> a (CondExpr a g et ef) -> a (AssignExpr a op lv e) -> a - (ParenExpr a e) -> a (ListExpr a es) -> a (CallExpr a fn params) -> a (FuncExpr a mid args s) -> a diff --git a/src/Language/ECMAScript3/Syntax/Arbitrary.hs b/src/Language/ECMAScript3/Syntax/Arbitrary.hs new file mode 100644 index 0000000..0705ed6 --- /dev/null +++ b/src/Language/ECMAScript3/Syntax/Arbitrary.hs @@ -0,0 +1,383 @@ +{-# LANGUAGE TemplateHaskell #-} +-- | QuickCheck $Arbitrary$ instances for ECMAScript 3 abstract +-- syntax. + +module Language.ECMAScript3.Syntax.Arbitrary where + +import Language.ECMAScript3.Syntax +import Test.QuickCheck hiding (Prop) +import Test.QuickCheck.Arbitrary +import Test.QuickCheck.Property (forAllShrink) +import Data.Map hiding (map,null,filter,foldr) +import Data.List (nub,delete) +import Data.Data +import Data.Char +import Data.Generics.Uniplate.Data +import Data.Generics.Uniplate.Operations +import Data.Generics.Str +import Control.Monad +import Control.Monad.State +import Data.Maybe (maybeToList) + +instance Arbitrary (AssignOp) where + arbitrary = + elements [OpAssign, OpAssignAdd, OpAssignSub, OpAssignMul, OpAssignDiv, + OpAssignMod, OpAssignLShift, OpAssignSpRShift, OpAssignZfRShift, + OpAssignBAnd, OpAssignBXor, OpAssignBOr] + +instance Arbitrary (InfixOp) where + arbitrary = + elements [OpLT, OpLEq, OpGT, OpGEq , OpIn , OpInstanceof, OpEq, OpNEq, + OpStrictEq, OpStrictNEq, OpLAnd, OpLOr, + OpMul, OpDiv, OpMod , OpSub, OpLShift, OpSpRShift, + OpZfRShift, OpBAnd, OpBXor, OpBOr, OpAdd] + +instance Arbitrary (UnaryAssignOp) where + arbitrary = + elements [PrefixInc, PrefixDec, PostfixInc, PostfixDec] + +instance Arbitrary (PrefixOp) where + arbitrary = + elements [PrefixLNot, PrefixBNot, PrefixPlus, PrefixMinus, + PrefixTypeof, PrefixVoid, PrefixDelete] + + +instance Arbitrary a => Arbitrary (Id a) where + arbitrary = liftM2 Id arbitrary identifier + shrink (Id a s) = [Id na ns | ns <- shrink s, na <- shrink a] + +instance Arbitrary a => Arbitrary (CaseClause a) where + arbitrary = oneof [caseclause, casedefault] + where caseclause = liftM3 CaseClause arbitrary arbitrary arbitrary + casedefault = liftM2 CaseDefault arbitrary arbitrary + shrink (CaseClause a expr stmts) = + [CaseClause na ne ns | na <- shrink a, ne <- shrink expr, ns <- shrink stmts] + shrink (CaseDefault a stmts) = + [CaseDefault na ns | na <- shrink a, ns <- shrink stmts] + +instance Arbitrary a => Arbitrary (Prop a) where + arbitrary = oneof [liftM2 PropId arbitrary arbitrary, + liftM2 PropString arbitrary nonEmptyString, + liftM2 PropNum arbitrary nonNegative + ] + shrink (PropId a id) = [PropId na nid | nid <- shrink id, na <- shrink a] + shrink (PropString a s) = [PropString na ns | ns <- shrink s, na <- shrink a] + shrink (PropNum a i) = [PropNum na ni | ni <- shrink i, na <- shrink a] + +instance Arbitrary a => Arbitrary (LValue a) where + arbitrary = oneof [liftM2 LVar arbitrary identifier, + liftM3 LDot arbitrary arbitrary identifier, + liftM3 LBracket arbitrary arbitrary arbitrary] + shrink (LVar a s) = [LVar na ns | ns <- shrink s, na <- shrink a] + shrink (LDot a e s) = [LDot na ne ns | ne <- shrink e, ns <-shrink s, na <-shrink a] + shrink (LBracket a e1 e2) = [LBracket na ne1 ne2 | ne1 <- shrink e1, ne2 <-shrink e2, na <- shrink a] + +cshrink :: Arbitrary a => [a] -> [a] +cshrink = concat . shrink + +identifier :: Gen String +identifier = sized sizedIdent + where sizedIdent n = do s <- identStart + rest <- identRest (n-1) + return (s:rest) + identStart = arbitrary `suchThat` isIdentStart + identRest n | n < 1 = return "" + identRest n = do p <- identPart + rest <- identRest (n-1) + return (p:rest) + identPart = do arbitrary `suchThat` isIdentPart + isIdentStart c = isLetter c || c == '$' || c == '_' + isIdentPart c = isIdentStart c || isMark c || isNumber c + +-- minimum size generator +type MSGen a = (Int, Gen a) + +sGen :: [MSGen a] -> Gen a +sGen gens = + sized f + where f n | n >= 0 = oneof $ map snd (filter (\(m, _) -> n >= m) gens) + f _ = f 0 + +recursive :: Gen a -> Gen a +recursive g = sized (\n -> resize (n-1) g) + +rarbitrary :: Arbitrary a => Gen a +rarbitrary = recursive arbitrary + +rrarbitrary :: Arbitrary a => Gen a +rrarbitrary = recursive $ recursive arbitrary + +atLeastOfSize :: Arbitrary a => Int -> Gen a -> Gen a +atLeastOfSize l gen = sized $ \s -> if s < l then resize l gen else gen + +nonEmptyString :: Gen String +nonEmptyString = sized $ \s -> if s < 1 then stringOfLength 1 else stringOfLength s + +regexpBody = nonEmptyString + +nonNegative :: (Arbitrary a, Num a) => Gen a +nonNegative = liftM abs arbitrary + +stringOfLength :: Int -> Gen String +stringOfLength 0 = return "" +stringOfLength n = do c <- arbitrary + rs <- stringOfLength (n-1) + return (c:rs) + +instance Arbitrary a => Arbitrary (Expression a) where + arbitrary = + sGen [(0, liftM ThisRef arbitrary), + (0, liftM NullLit arbitrary), + (0, liftM2 StringLit arbitrary arbitrary), + (0, liftM2 NumLit arbitrary nonNegative), + (0, liftM2 IntLit arbitrary nonNegative), + (0, liftM2 BoolLit arbitrary arbitrary), + (0, liftM4 RegexpLit arbitrary regexpBody arbitrary arbitrary), + (1, liftM2 ArrayLit arbitrary rarbitrary), + (1, liftM2 ObjectLit arbitrary rarbitrary), + (0, liftM2 VarRef arbitrary arbitrary), + (1, liftM3 DotRef arbitrary rarbitrary arbitrary), + (2, liftM3 BracketRef arbitrary rarbitrary rarbitrary), + (3, liftM3 NewExpr arbitrary rarbitrary rrarbitrary), + (1, liftM3 PrefixExpr arbitrary arbitrary rarbitrary), + (2, liftM3 UnaryAssignExpr arbitrary arbitrary rarbitrary), + (2, liftM4 InfixExpr arbitrary arbitrary rarbitrary rarbitrary), + (3, liftM4 CondExpr arbitrary rarbitrary rarbitrary rarbitrary), + (3, liftM4 AssignExpr arbitrary rarbitrary rarbitrary rarbitrary), + (3, liftM2 ListExpr arbitrary (recursive (atLeastOfSize 2 arbitrary))), + (3, liftM3 CallExpr arbitrary rarbitrary rrarbitrary), + (1, liftM4 FuncExpr arbitrary arbitrary arbitrary rarbitrary)] + + shrink (StringLit a s) = [StringLit na ns | na <- shrink a, ns <- shrink s] + shrink (RegexpLit a s b1 b2) = [RegexpLit na ns nb1 nb2 | na <- shrink a, nb1 <- shrink b1, nb2 <- shrink b2, ns <- shrink s] + shrink (NumLit a d) = [NumLit na nd | na <- shrink a, nd <- shrink d] + shrink (IntLit a i) = [IntLit na ni | na <- shrink a, ni <- shrink i] + shrink (BoolLit a b) = [BoolLit na nb | na <- shrink a, nb <- shrink b] + shrink (NullLit a) = [NullLit na | na <- shrink a] + shrink (ArrayLit a xs) = (cshrink xs) ++ xs ++ [ArrayLit na nxs | na <- shrink a, nxs <- shrink xs] + shrink (ObjectLit a xs) = + let es = map snd xs in + (cshrink es) ++ es ++ + [ObjectLit na nxs | na <- shrink a, nxs <- shrink xs] + shrink (ThisRef a) = [ThisRef na | na <- shrink a] + shrink (VarRef a id) = [VarRef na nid | na <- shrink a, nid <- shrink id] + shrink (DotRef a e id) = [DotRef na ne nid | na <-shrink a, nid <- shrink id, ne <- shrink e] + shrink (BracketRef a o k) = [BracketRef na no nk | na <- shrink a, no <-shrink o, nk <- shrink k] + shrink (NewExpr a c xs) = (shrink c) ++ [c] ++ (cshrink xs) ++ xs ++ [NewExpr na nc nxs | na <- shrink a, nc <- shrink c, nxs <- shrink xs] + shrink (PrefixExpr a op e) = (shrink e) ++ [e] ++ [PrefixExpr na nop ne | na <- shrink a, nop <-shrink op, ne <- shrink e] + shrink (UnaryAssignExpr a op v) = [UnaryAssignExpr na nop nv | na <- shrink a, nop <- shrink op, nv <- shrink v] + shrink (InfixExpr a op e1 e2) = (shrink e1) ++ [e1] ++ (shrink e2) ++ [e2] ++ [InfixExpr na nop ne1 ne2 | na <- shrink a, nop <- shrink op, ne1 <- shrink e1, ne2 <- shrink e2] + shrink (CondExpr a e1 e2 e3) = (shrink e1) ++ [e1] ++ (shrink e2) ++ [e2] ++ (shrink e3) ++ [e3] ++ [CondExpr na ne1 ne2 ne3 | na <- shrink a, ne1 <- shrink e1, ne2 <- shrink e2, ne3 <- shrink e3] + shrink (AssignExpr a op v e) = (shrink e) ++ [e] ++ [AssignExpr na nop nv ne | na <- shrink a, nop <- shrink op, nv <- shrink v, ne <-shrink e] + shrink (ListExpr a es) = (cshrink es) ++ es ++ [ListExpr na nes | na <- shrink a, nes <- shrink es] + shrink (CallExpr a e es) = (shrink e) ++ [e] ++ (cshrink es) ++ es ++ [CallExpr na ne nes | na <- shrink a, ne <- shrink e, nes <- shrink es] + shrink (FuncExpr a mid ids s) = [FuncExpr na nmid nids ns | na <- shrink a, nmid <- shrink mid, nids <- shrink ids, ns <- shrink s] + +instance Arbitrary a => Arbitrary (ForInInit a) where + arbitrary = oneof [liftM ForInVar arbitrary, + liftM ForInLVal arbitrary] + shrink (ForInVar id) = [ForInVar nid | nid <- shrink id] + shrink (ForInLVal id) = [ForInLVal nid | nid <- shrink id] + +instance Arbitrary a => Arbitrary (ForInit a) where + arbitrary = + frequency [ + (2, return NoInit), + (1, liftM VarInit arbitrary), + (1, liftM ExprInit arbitrary)] + shrink (NoInit) = [] + shrink (VarInit vds) = [VarInit nvds | nvds <- shrink vds] + shrink (ExprInit e) = [ExprInit ne | ne <- shrink e] + +instance Arbitrary a => Arbitrary (CatchClause a) where + arbitrary = liftM3 CatchClause arbitrary arbitrary arbitrary + shrink (CatchClause a id s) = [CatchClause na nid ns | na <- shrink a, nid <- shrink id, ns <- shrink s] + +instance Arbitrary a => Arbitrary (VarDecl a) where + arbitrary = liftM3 VarDecl arbitrary arbitrary arbitrary + shrink (VarDecl a id me) = [VarDecl na nid nme | na <- shrink a, nid <- shrink id, nme <- shrink me] + +instance Arbitrary a => Arbitrary (Statement a) where + arbitrary = + sGen [(2, liftM2 BlockStmt arbitrary rrarbitrary), + (0, liftM EmptyStmt arbitrary), + (1, liftM2 ExprStmt arbitrary rarbitrary), + (3, liftM4 IfStmt arbitrary rarbitrary rarbitrary rarbitrary), + (2, liftM3 IfSingleStmt arbitrary rarbitrary rarbitrary), + (3, liftM3 SwitchStmt arbitrary rarbitrary rrarbitrary), + (2, liftM3 WhileStmt arbitrary rarbitrary rarbitrary), + (2, liftM3 DoWhileStmt arbitrary rarbitrary rarbitrary), + (0, liftM2 BreakStmt arbitrary arbitrary), + (0, liftM2 ContinueStmt arbitrary arbitrary), + (1, liftM3 LabelledStmt arbitrary arbitrary rarbitrary), + (3, liftM4 ForInStmt arbitrary rarbitrary rarbitrary rarbitrary), + (4, liftM5 ForStmt arbitrary rarbitrary rarbitrary rarbitrary rarbitrary), + (4, arbtry), + (1, liftM2 ThrowStmt arbitrary rarbitrary), + (1, liftM2 ReturnStmt arbitrary rarbitrary), + (2, liftM3 WithStmt arbitrary rarbitrary rarbitrary), + (2, liftM2 VarDeclStmt arbitrary rrarbitrary), + (1, liftM4 FunctionStmt arbitrary arbitrary arbitrary rarbitrary)] + where arbtry = + do (mCatch, mFinally) <- oneof [liftM2 (,) (return Nothing) (liftM Just rarbitrary), + liftM2 (,) (liftM Just rarbitrary) (return Nothing), + liftM2 (,) (liftM Just rarbitrary) (liftM Just rarbitrary)] + a <- arbitrary + body <- rarbitrary + return $ TryStmt a body mCatch mFinally + + shrink (BlockStmt a body) = emptyStmtShrink a ++ + [BlockStmt as bs | as <- shrink a, bs <- shrink body] + shrink (EmptyStmt a) = emptyStmtShrink a + shrink (ExprStmt a e) = emptyStmtShrink a ++ + [ExprStmt as es | as <- shrink a, es <- shrink e] + shrink (IfStmt a e th el) = emptyStmtShrink a ++ + [IfStmt as es ths els | as <- shrink a, es <- shrink e, ths <- shrink th, els <- shrink el] + shrink (IfSingleStmt a e th) = emptyStmtShrink a ++ + [IfSingleStmt as es ths | as <- shrink a, es <- shrink e, ths <- shrink th] + shrink (SwitchStmt a e cases) = emptyStmtShrink a ++ + [SwitchStmt as es cs | as <- shrink a, es <-shrink e, cs <- shrink cases] + shrink (WhileStmt a e b) = emptyStmtShrink a ++ + [WhileStmt as es bs | as <- shrink a, es <- shrink e, bs <- shrink b] + shrink (DoWhileStmt a b e) = emptyStmtShrink a ++ + [DoWhileStmt as bs es | as <- shrink a, es <- shrink e, bs <- shrink b] + shrink (BreakStmt a l) = emptyStmtShrink a ++ + [BreakStmt as ls | as <- shrink a, ls <- shrink l] + shrink (ContinueStmt a l) = emptyStmtShrink a ++ + [ContinueStmt as ls | as <- shrink a, ls <- shrink l] + shrink (LabelledStmt a l s) = emptyStmtShrink a ++ + [LabelledStmt as ls ss | as <- shrink a, ls <- shrink l, ss <- shrink s] + shrink (ForInStmt a i o s) = emptyStmtShrink a ++ + [ForInStmt as is os ss | as <- shrink a, is <-shrink i, os <-shrink o, ss <- shrink s] + shrink (ForStmt a i e1 e2 s) = emptyStmtShrink a ++ + [ForStmt as is e1s e2s ss | as <- shrink a, is <- shrink i, e1s <- shrink e1, e2s <- shrink e2, ss <- shrink s] + shrink (TryStmt a b cs mf) = emptyStmtShrink a ++ + [TryStmt as bs css mfs | as <- shrink a, bs <- shrink b, css <- shrink cs, mfs <- shrink mf] + shrink (ThrowStmt a e) = emptyStmtShrink a ++ + [ThrowStmt as es | as <- shrink a, es <- shrink e] + shrink (ReturnStmt a e) = emptyStmtShrink a ++ + [ReturnStmt as es | as <- shrink a, es <- shrink e] + shrink (WithStmt a o s) = emptyStmtShrink a ++ + [WithStmt as os ss | as <- shrink a, os <- shrink o, ss <- shrink s] + shrink (VarDeclStmt a vds) = emptyStmtShrink a ++ + [VarDeclStmt as vdss | as <- shrink a, vdss <- shrink vds] + shrink (FunctionStmt a n pars b) = emptyStmtShrink a ++ + [FunctionStmt as ns parss bs | as <- shrink a, ns <- shrink n, parss <- shrink pars, bs <- shrink b] + +emptyStmtShrink a = [EmptyStmt a2 | a2 <- shrink a] + +type LabelSubst = Map (Id ()) (Id ()) +emptyConstantPool = Data.Map.empty + +instance (Data a, Arbitrary a) => Arbitrary (JavaScript a) where + arbitrary = do {s <- liftM2 Script arbitrary arbitrary; + if isProgramFixable s then fixLabels s + else arbitrary} + shrink (Script a ss) = [Script na nss | na <- shrink a, nss <- shrink ss] + +-- | Fixes labels so that labeled breaks and continues refer to +-- existing labeled statements, enclosing them; also, reduces the size +-- of the label set. Assumes that the program has a proper syntactic +-- structure, i.e. 'isProgramFixable' s = True. +fixLabels :: (Data a) => JavaScript a -> Gen (JavaScript a) +fixLabels s = + fixBreakContinueLabels s >>= removeDuplicateLabels + +-- | choose n elements from a list randomly +rChooseElem :: [a] -> Int -> Gen [a] +rChooseElem xs n | n > 0 && (not $ null xs) = + if n >= length xs then return xs + else (vectorOf n $ choose (0, n-1)) >>= + (\subst -> return $ foldr (\n ys -> (xs!!n):ys) [] subst) +rChooseElem _ _ = return [] + +-- | A predicate that tells us whether a program has a fixable/correct +-- label-break/continue structure. The predicate imposes syntactic +-- restrictions on the break, continue and labeled statements as in +-- the ECMA spec +isProgramFixable :: (Data a ) => JavaScript a -> Bool +isProgramFixable (Script _ stmts) = + Prelude.and $ + Prelude.map + (\stmt -> isBreakContinueFixable stmt False False False) + stmts + +-- | Imposes relaxed restrictions on break and continue per ECMAScript +-- 5 spec (page 92): any continue without a label should be nested +-- within an iteration stmt, any continue with a label should be +-- nested in a labeled statement (not necessarily with the same +-- label); any break statement without a label should be nested in an +-- iteration or switch stmt, any break statement with a label should +-- be nested in a labeled statement (not necessarily with the same +-- label). +isBreakContinueFixable :: (Data a) => Statement a -> + Bool -> + Bool -> + Bool -> + Bool +isBreakContinueFixable stmt inLabeled inIter inSwitch = + case stmt of + ContinueStmt _ Nothing -> inIter + ContinueStmt _ (Just label) -> inLabeled + BreakStmt _ Nothing -> inIter || inSwitch + BreakStmt _ (Just label) -> inLabeled + LabelledStmt _ label _ -> + continue stmt True inIter inSwitch + _ -> if isIterationStmt stmt then + continue stmt inLabeled True inSwitch + else if isSwitchStmt stmt then + continue stmt inLabeled inIter True + else True + -- _ -> continue stmt inLabeled inIter inSwitch + where continue stmt inLabeled inIter inSwitch = + and $ map (\s -> isBreakContinueFixable s inLabeled inIter inSwitch) (children stmt) + +-- | Removes duplicate labels from nested labeled statements in order +-- to impose restrictions on labeled statements as per ECMAScript 5 +-- spec (page 95): nested labeled statements cannot have duplicating +-- labels. +removeDuplicateLabels :: Data a => JavaScript a -> Gen (JavaScript a) +removeDuplicateLabels (Script x stmts) = + return $ Script x (map (\stmt -> (evalState (transformM removeDL stmt) [])) stmts) + where + removeDL :: Statement a -> State [String] (Statement a) + removeDL stmt@(LabelledStmt x lab s) = + do {enclosingLabels <- get; + if Prelude.elem (unId lab) enclosingLabels then return s + else modify ((:) $ unId lab) >> return stmt} + removeDL s = return s + +-- | Selects a random element of the list +selectRandomElement :: [a] -> Gen a +selectRandomElement xs = + let l = length xs in + do n <- arbitrary + return $ xs !! (n `mod` l - 1) +-- | Changes labels of break/continue so that they refer to one of the +-- enclosing labels +fixBreakContinueLabels :: Data a => JavaScript a -> Gen (JavaScript a) +fixBreakContinueLabels (Script x stmts) = + do stmts2 <- mapM (\stmt -> (evalStateT (fixBCL stmt) [])) stmts + return $ Script x stmts2 + where + fixBCL :: Data a => Statement a -> StateT [String] Gen (Statement a) + fixBCL stmt@(LabelledStmt _ lab s) = + do modify ((:) $ unId lab) + descendM fixBCL stmt + fixBCL stmt@(BreakStmt x (Just (Id y lab))) = + do {labels <- get; + if lab `notElem` labels then + do {newLab <- lift $ selectRandomElement labels; + return $ BreakStmt x (Just $ Id y newLab)} + else return stmt} + fixBCL stmt@(ContinueStmt x (Just (Id y lab))) = + do {labels <- get; + if lab `notElem` labels then + do {newLab <- lift $ selectRandomElement labels; + return $ ContinueStmt x (Just $ Id y newLab)} + else return stmt} + fixBCL s = return s + +isSwitchStmt :: Statement a -> Bool +isSwitchStmt (SwitchStmt _ _ _) = True +isSwitchStmt _ = False
\ No newline at end of file diff --git a/src/PrettyTest.hs b/src/PrettyTest.hs new file mode 100644 index 0000000..ffd9c59 --- /dev/null +++ b/src/PrettyTest.hs @@ -0,0 +1,30 @@ +module Main where + +import Language.ECMAScript3.Parser +import Language.ECMAScript3.PrettyPrint +import Language.ECMAScript3.Syntax +import Language.ECMAScript3.Syntax.Arbitrary +import Language.ECMAScript3.Syntax.Annotations +import Test.QuickCheck +import System.Exit + + + +main = + let qcArgs = Args {maxSuccess = 50 + ,maxDiscardRatio = 10 + ,maxSize = 10 + ,replay = Nothing + ,chatty = True} + in quickCheckWithResult qcArgs prettyParseEquivalence >>= \res -> + case res of + Success {} -> putStrLn "All tests passes" + GaveUp {} -> putStrLn "Gave up" + Failure {} -> putStrLn "Test failed" >> exitFailure + NoExpectedFailure {} -> putStrLn "Unexpected failure" >> exitFailure + +prettyParseEquivalence :: JavaScript () -> Bool +prettyParseEquivalence js = + case parseScriptFromString "" $ show $ javaScript js of + Left _ -> False + Right parsed -> (reannotate (const ()) parsed) == js
\ No newline at end of file diff --git a/src/UnitTest.hs b/src/UnitTest.hs index 27c34c8..bb10062 100644 --- a/src/UnitTest.hs +++ b/src/UnitTest.hs @@ -10,6 +10,8 @@ import Language.ECMAScript3.Syntax testDir = "tests/parse-pretty" + +-- | tests the parser with pre-defined test-cases parsePrettyTest filename = TestLabel filename $ TestCase $ do js <- parseJavaScriptFromFile filename let str = renderStatements js diff --git a/tests/parse-pretty/flapjax-fxinternal-22dec2008.js b/tests/parse-pretty/flapjax-fxinternal-22dec2008.js index 272499a..43d1c6e 100644 --- a/tests/parse-pretty/flapjax-fxinternal-22dec2008.js +++ b/tests/parse-pretty/flapjax-fxinternal-22dec2008.js @@ -1,8 +1,8 @@ function flapjaxInit(options) { // compress via http://alex.dojotoolkit.org/shrinksafe/ - // make sure to change final eval call to use exported library renamed + // make sure to change final eval call to use exported library renamed // name - + var defaultOptions = { includeSynonyms: true, exportMisc: true, @@ -12,9 +12,9 @@ function flapjaxInit(options) { exportWS: true, hide: [ ], show: [ ], - redefine: false, + redefine: false }; - + if (options === false) { options = { hide: [ ], show: [ ] }; } @@ -28,7 +28,7 @@ function flapjaxInit(options) { options[option] = defaultOptions[option]; } }; - + // Transform hide and show lists into tables var hideArray = options.hide; options.hide = { }; @@ -40,26 +40,26 @@ function flapjaxInit(options) { for (var i = 0; i < showArray.length; i++) { options.show[showArray[i]] = true; } - + var warn = function(s) { /*if (console && console.warn) { console.warn(s); }*/ }; - - - var flapjax = { - version: 4, + + + var flapjax = { + version: 4, base: {}, //pulses combinators: {}, // combinators yielding nodes behaviours: {}, dom: {} // dom convenience methods and combinators }; - + var d = flapjax.dom; - + flapjax.pub = {util:flapjax}; - + var annotate = function(fn,names,protoArg,protoObjs,protoNames) { for(var i=0; i<names.length;i++) { flapjax.pub[names[i]] = fn; @@ -69,15 +69,15 @@ function flapjaxInit(options) { var args = slice(arguments,0); args.splice(protoArg,0,this); return fn.apply(this,args); - } + }; for(var i=0; i<protoObjs.length; i++) { for(var j=0; j<protoNames.length;j++) { protoObjs[i][protoNames[j]] = pf; } } } - } - + }; + var exports = { }; var synonyms = { }; @@ -86,7 +86,7 @@ function flapjaxInit(options) { var dom = { }; /* Used as a symbol */ var domMisc = { }; /* Used as a symbol */ var ws = { }; /* Used as a symbol */ - + var fxExport = function(exportCategory,exportVal, exportName /* , synonyms */) { if (!(exportCategory instanceof Object)) { @@ -95,7 +95,7 @@ function flapjaxInit(options) { if (typeof(exportName) != 'string') { console.log(exportVal); - throw 'fxExport: name is ' + exportName; + throw 'fxExport: name is ' + exportName; }; exportVal.__flapjaxCategory = exportCategory; @@ -104,8 +104,8 @@ function flapjaxInit(options) { exports[arguments[i]] = exportVal; synonyms[arguments[i]] = true; } - } - + }; + var fxMethodSynonyms = function(obj,method) { if (options.includeSynonyms === true) { for (var i = 2; i < arguments.length; i++) { @@ -113,10 +113,10 @@ function flapjaxInit(options) { }; }; }; - + ////////////////////////////////////////////////////////////////////////////// // Miscellaneous functions - + //credit 4umi //slice: Array a * Integer * Integer -> Array a var slice = function (arr, start, stop) { @@ -128,7 +128,7 @@ function flapjaxInit(options) { for( i = 0; i < stop - start; i++ ) { r[i] = arr[start+i]; } return r; } - + var isEqual = function (a,b) { return (a == b) || ( (((typeof(a) == 'number') && isNaN(a)) || a == 'NaN') && @@ -137,22 +137,22 @@ function flapjaxInit(options) { //member: a * Array b -> Boolean var member = function(elt, lst) { - for (var i = 0; i < lst.length; i++) { - if (isEqual(lst[i], elt)) {return true;} + for (var i = 0; i < lst.length; i++) { + if (isEqual(lst[i], elt)) {return true;} } return false; }; - + var zip = function(arrays) { if (arrays.length == 0) return []; var ret = []; for(var i=0; i<arrays[0].length;i++) { ret.push([]); - for(var j=0; j<arrays.length;j++) + for(var j=0; j<arrays.length;j++) ret[i].push(arrays[j][i]); } return ret; - } + }; //map: (a * ... -> z) * [a] * ... -> [z] var map = function (fn) { @@ -170,16 +170,16 @@ function flapjaxInit(options) { return ret; } }; - + //filter: (a -> Boolean) * Array a -> Array a var filter = function (predFn, arr) { var res = []; - for (var i = 0; i < arr.length; i++) { + for (var i = 0; i < arr.length; i++) { if (predFn(arr[i])) { res.push(arr[i]); } } return res; }; - + //fold: (a * .... * accum -> accum) * accum * [a] * ... -> accum //fold over list(s), left to right var fold = function(fn, init /* arrays */) { @@ -195,7 +195,7 @@ function flapjaxInit(options) { else { var acc = init; for (var i = 0; i < lists[0].length; i++) { - var args = map( function (lst) { return lst[i];}, + var args = map( function (lst) { return lst[i];}, lists); args.push(acc); acc = fn.apply({}, args); @@ -203,7 +203,7 @@ function flapjaxInit(options) { return acc; } }; - + //foldR: (a * .... * accum -> accum) * accum * [a] * ... -> accum //fold over list(s), right to left, fold more memory efficient (left to right) var foldR = function (fn, init /* arrays */) { @@ -218,22 +218,22 @@ function flapjaxInit(options) { else { var acc = init; for (var i = lists[0].length - 1; i > -1; i--) { - var args = map( function (lst) { return lst[i];}, + var args = map( function (lst) { return lst[i];}, lists); args.push(acc); acc = fn.apply({}, args); } - return acc; + return acc; } }; - + var pushAll = function(destArray,srcArray) { for (var i = 0; i < srcArray.length; i++) { destArray.push(srcArray[i]); } return destArray; }; - + fxExport(misc,slice,'slice'); fxExport(misc,member,'member'); fxExport(misc,map,'map'); @@ -241,10 +241,10 @@ function flapjaxInit(options) { fxExport(misc,filter,'filter'); fxExport(misc,fold,'fold'); fxExport(misc,foldR,'foldR'); - + ////////////////////////////////////////////////////////////////////////////// // Flapjax core - + //Pulse: Stamp * Path * Obj var Pulse = function (stamp, value) { this.stamp = stamp; @@ -266,8 +266,8 @@ function flapjaxInit(options) { ctx.val[kvpos] = kv; } }; - this.isEmpty = function () { - return ctx.val.length === 0; + this.isEmpty = function () { + return ctx.val.length === 0; }; this.pop = function () { if(ctx.val.length == 1) { @@ -296,13 +296,13 @@ function flapjaxInit(options) { return ret; }; }; - + var lastRank = 0; var stamp = 1; var nextStamp = function () { return ++stamp; }; - - //propagatePulse: Pulse * Array Node -> - //Send the pulse to each node + + //propagatePulse: Pulse * Array Node -> + //Send the pulse to each node var propagatePulse = function (pulse, node) { var queue = new PQ(); //topological queue for current timestep queue.insert({k:node.rank,n:node,v:pulse}); @@ -314,36 +314,36 @@ function flapjaxInit(options) { },new Pulse(qv.v.stamp,qv.v.value)); } }; - + //Event: Array Node b * ( (Pulse a -> Void) * Pulse b -> Void) var EventStream = function (nodes,updater) { this.updater = updater; - + this.sendsTo = []; //forward link - + for (var i = 0; i < nodes.length; i++) { nodes[i].sendsTo.push(this); } - + this.rank = ++lastRank; }; EventStream.prototype = new Object(); - + fxExport(core,EventStream,'EventStream'); - - + + //createNode: Array Node a * ( (Pulse b ->) * (Pulse a) -> Void) -> Node b var createNode = function (nodes, updater) { return new EventStream(nodes,updater); }; - + //attachListenerNode: Node * Node -> Voids //flow from node to dependent //note: does not add flow as counting for rank nor updates parent ranks var attachListener = function (node, dependent) { if (!(node instanceof EventStream)) { throw 'attachListenenerNode: expects event as first arg';} //SAFETY if (!(dependent instanceof EventStream)) { throw 'attachListenenerNode: expects event as second arg';} //SAFETY - + node.sendsTo.push(dependent); if(node.rank > dependent.rank) { var lowest = lastRank+1; @@ -355,7 +355,7 @@ function flapjaxInit(options) { } } }; - + //removeListenerNode: Node * Node -> Boolean //remove flow from node to dependent //note: does not remove flow as counting for rank nor updates parent ranks @@ -363,7 +363,7 @@ function flapjaxInit(options) { { if (!(node instanceof EventStream)) { throw 'removeListenerNode: expects event as first arg';} //SAFETY if (!(dependent instanceof EventStream)) { throw 'removeListenenerNode: expects event as second arg';} //SAFETY - + var foundSending = false; for (var i = 0; i < node.sendsTo.length && !foundSending; i++) { if (node.sendsTo[i] == dependent) { @@ -371,23 +371,23 @@ function flapjaxInit(options) { foundSending = true; } } - + return foundSending; }; - - // An internal_e is a node that simply propagates all pulses it receives. It's used internally by various + + // An internal_e is a node that simply propagates all pulses it receives. It's used internally by various // combinators. var internal_e = function(dependsOn) { return createNode(dependsOn || [ ],function(send,pulse) { send(pulse); }); } - + var zero_e = function() { return createNode([],function(send,pulse) { throw ('zero_e : received a value; zero_e should not receive a value; the value was ' + pulse.value); }); }; fxExport(core,zero_e,'zero_e'); - + var one_e = function(val) { var sent = false; var evt = createNode([],function(send,pulse) { @@ -401,7 +401,7 @@ function flapjaxInit(options) { return evt; }; fxExport(core,one_e,'one_e'); - + // a.k.a. mplus; merge_e(e1,e2) == merge_e(e2,e1) var merge_e = function() { if (arguments.length == 0) { @@ -428,10 +428,10 @@ function flapjaxInit(options) { }); }; fxMethodSynonyms(EventStream,'constant_e','constant','replaceValue_e','replaceValue'); - + var constant_e = function(e) { return e.constant_e(); }; fxExport(core,constant_e,'constant_e','replaceValue_e'); - + var createTimeSyncNode = function(nodes) { var nqs = map(function(n) { var qpulse = []; @@ -445,32 +445,32 @@ function flapjaxInit(options) { s(p); }}); }; - + //This is up here so we can add things to its prototype that are in flapjax.combinators var Behaviour = function (event, init, updater) { - if (!(event instanceof EventStream)) { - throw 'Behaviour: expected event as second arg'; + if (!(event instanceof EventStream)) { + throw 'Behaviour: expected event as second arg'; } - + var behave = this; this.last = init; - + //sendEvent to this might impact other nodes that depend on this event //sendBehaviour defaults to this one this.underlyingRaw = event; - + //unexposed, sendEvent to this will only impact dependents of this behaviour this.underlying = createNode( - [event], - (updater ? - function (s, p) {behave.last = updater(p.value); p.value = behave.last; s(p);} : + [event], + (updater ? + function (s, p) {behave.last = updater(p.value); p.value = behave.last; s(p);} : function (s, p) {behave.last = p.value; s(p);})); }; Behaviour.prototype = new Object(); fxExport(core,Behaviour,'Behaviour'); fxExport(core,Behaviour,'Behavior'); - + var receiver_e = function() { var evt = internal_e(); evt.sendEvent = function(value) { @@ -479,16 +479,16 @@ function flapjaxInit(options) { return evt; }; fxExport(core,receiver_e,'receiver_e'); - + //note that this creates a new timestamp and new event queue var sendEvent = function (node, value) { if (!(node instanceof EventStream)) { throw 'sendEvent: expected Event as first arg'; } //SAFETY - + propagatePulse(new Pulse(nextStamp(), value),node); }; fxExport(core,sendEvent,'sendEvent'); synonyms['sendEvent'] = true; // Hack: sendEvent simply should not be exported; calling it a synonym deprecates it. - + // bind_e :: EventStream a * (a -> EventStream b) -> EventStream b EventStream.prototype.bind_e = function(k) { /* m.sendsTo result_e @@ -497,12 +497,12 @@ function flapjaxInit(options) { */ var m = this; var prev_e = false; - + var out_e = createNode([],function(send,pulse) { send(pulse); }); out_e.name = "bind out_e"; - + var in_e = createNode([m], function (send,pulse) { - if (prev_e) { + if (prev_e) { removeListener(prev_e,out_e); } prev_e = k(pulse.value); @@ -514,7 +514,7 @@ function flapjaxInit(options) { } }); in_e.name = "bind in_e"; - + return out_e; }; @@ -526,7 +526,7 @@ function flapjaxInit(options) { if (!(f instanceof Function)) { throw ('lift_e : expected a function as the first argument; received ' + f); }; - + return createNode([this],function(send,pulse) { pulse.value = f(pulse.value); send(pulse); @@ -534,18 +534,18 @@ function flapjaxInit(options) { }; fxMethodSynonyms(EventStream,'lift_e', 'transform_e','map_e','apply_e','lift','transform','map','apply'); - + EventStream.prototype.not_e = function() { return this.lift_e(function(v) { return !v; }); }; fxMethodSynonyms(EventStream,'not_e','not'); - + var not_e = function(e) { return e.not_e(); }; fxExport(core,not_e,'not_e','not'); - + EventStream.prototype.filter_e = function(pred) { if (!(pred instanceof Function)) { throw ('filter_e : expected predicate; received ' + pred); }; - + // Can be a bind_e return createNode([this], function(send,pulse) { @@ -553,10 +553,10 @@ function flapjaxInit(options) { }); }; fxMethodSynonyms(EventStream,'filter_e','filter'); - + var filter_e = function(e,p) { return e.filter_e(p); }; fxExport(core,filter_e,'filter_e'); - + // Fires just once. EventStream.prototype.once_e = function() { var done = false; @@ -565,11 +565,11 @@ function flapjaxInit(options) { if (!done) { done = true; send(pulse); } }); }; - fxMethodSynonyms(EventStream,'once_e','once') - + fxMethodSynonyms(EventStream,'once_e','once'); + var once_e = function(e) { return e.once_e(); }; fxExport(core,once_e,'once_e'); - + EventStream.prototype.skipFirst_e = function() { var skipped = false; return createNode([this],function(send,pulse) { @@ -580,10 +580,10 @@ function flapjaxInit(options) { }); }; fxMethodSynonyms(EventStream,'skipFirst_e','skipFirst'); - + var skipFirst_e = function(e) { return e.skipFirst_e(); }; fxExport(core,skipFirst_e,'skipFirst_e'); - + EventStream.prototype.collect_e = function(init,fold) { var acc = init; return this.lift_e( @@ -594,31 +594,31 @@ function flapjaxInit(options) { }); }; fxMethodSynonyms(EventStream,'collect_e','collect','transformWithMemory'); - + var collect_e = function(e,i,f) { return e.collect_e(i,f); }; fxExport(core,collect_e,'collect_e'); - + // a.k.a. join EventStream.prototype.switch_e = function() { return this.bind_e(function(v) { return v; }); }; fxMethodSynonyms(EventStream,'switch_e','forwardLatest'); - + var switch_e = function(e) { return e.switch_e(); }; fxExport(core,switch_e,'switch_e'); - + EventStream.prototype.if_e = function(thenE,elseE) { var testStamp = -1; var testValue = false; - + createNode([this],function(_,pulse) { testStamp = pulse.stamp; testValue = pulse.value; }); - + return merge_e( createNode([thenE],function(send,pulse) { if (testValue && (testStamp == pulse.stamp)) { send(pulse); } }), createNode([elseE],function(send,pulse) { if (!testValue && (testStamp == pulse.stamp)) { send(pulse); } })); }; fxMethodSynonyms(EventStream,'if_e','choose_e','choose'); - + var if_e = function(test,thenE,elseE) { if (test instanceof EventStream) { return test.if_e(thenE,elseE); } @@ -626,43 +626,43 @@ function flapjaxInit(options) { { return test ? thenE : elseE; } }; fxExport(core,if_e,'if_e','choose_e'); - + var cond_e = function (/*. predValArrays */) { var predValArrays = slice(arguments, 0); var acc = zero_e(); for (var i = predValArrays.length - 1; i > -1; i--) { acc = if_e(predValArrays[i][0],predValArrays[i][1], acc); } - return acc; + return acc; }; fxExport(core,cond_e,'cond_e'); - + var and_e = function (/* . nodes */) { var nodes = slice(arguments, 0); - - var acc = (nodes.length > 0)? + + var acc = (nodes.length > 0)? nodes[nodes.length - 1] : one_e(true); - + for (var i = nodes.length - 2; i > -1; i--) { acc = if_e( - nodes[i], - acc, + nodes[i], + acc, nodes[i].constant_e(false)); } return acc; }; fxExport(core,and_e,'and_e'); - + EventStream.prototype.and_e = function( /* others */ ) { var deps = [this].concat(slice(arguments,0)); return and_e.apply(this,deps); }; fxMethodSynonyms(EventStream,'and_e','and'); - + var or_e = function () { var nodes = slice(arguments, 0); - var acc = (nodes.length > 2)? - nodes[nodes.length - 1] : one_e(false); + var acc = (nodes.length > 2)? + nodes[nodes.length - 1] : one_e(false); for (var i = nodes.length - 2; i > -1; i--) { acc = if_e( nodes[i], @@ -672,72 +672,72 @@ function flapjaxInit(options) { return acc; }; fxExport(core,or_e,'or_e'); - + EventStream.prototype.or_e = function(/*others*/) { var deps = [this].concat(slice(arguments,0)); return or_e.apply(this,deps); }; fxMethodSynonyms(EventStream,'or_e','or'); - + var delayStatic_e = function (event, time) { - + var resE = internal_e(); - + createNode( [event], - function (s, p) { - setTimeout( - function () { sendEvent(resE, p.value);}, + function (s, p) { + setTimeout( + function () { sendEvent(resE, p.value);}, time ); }); - + return resE; }; - + //delay_e: Event a * [Behaviour] Number -> Event a EventStream.prototype.delay_e = function (time) { var event = this; - + if (time instanceof Behaviour) { - + var receiverEE = internal_e(); - var link = + var link = { - from: event, + from: event, towards: delayStatic_e(event, valueNow(time)) }; - + //TODO: Change semantics such that we are always guaranteed to get an event going out? - var switcherE = + var switcherE = createNode( [changes(time)], function (s, p) { - removeListener(link.from, link.towards); + removeListener(link.from, link.towards); link = { - from: event, + from: event, towards: delayStatic_e(event, p.value) }; sendEvent(receiverEE, link.towards); }); - + var resE = receiverEE.switch_e(); - + sendEvent(switcherE, valueNow(time)); return resE; - + } else { return delayStatic_e(event, time); } }; fxMethodSynonyms(EventStream,'delay_e','delay'); - + var delay_e = function(sourceE,interval) { return sourceE.delay_e(interval); }; fxExport(core,delay_e,'delay_e'); - + //lift_e: ([Event] (. Array a -> b)) . Array [Event] a -> [Event] b var lift_e = function (fn /*, [node0 | val0], ...*/) { // if (!(fn instanceof Function)) { throw 'lift_e: expected fn as second arg'; } //SAFETY - + var valsOrNodes = slice(arguments, 0); //selectors[i]() returns either the node or real val, optimize real vals var selectors = []; @@ -746,26 +746,26 @@ function flapjaxInit(options) { for (var i = 0; i < valsOrNodes.length; i++) { if (valsOrNodes[i] instanceof EventStream) { nodes.push(valsOrNodes[i]); - selectors.push( + selectors.push( (function(ii) { - return function(realArgs) { + return function(realArgs) { return realArgs[ii]; }; })(selectI)); selectI++; } else { - selectors.push( - (function(aa) { + selectors.push( + (function(aa) { return function () { return aa; - }; + }; })(valsOrNodes[i])); - } + } } - + var context = this; var nofnodes = slice(selectors,1); - + if (nodes.length === 0) { return one_e(fn.apply(context, valsOrNodes)); } else if ((nodes.length === 1) && (fn instanceof Function)) { @@ -773,7 +773,7 @@ function flapjaxInit(options) { function () { var args = arguments; return fn.apply( - context, + context, map(function (s) {return s(args);}, nofnodes)); }); } else if (nodes.length === 1) { @@ -781,9 +781,9 @@ function flapjaxInit(options) { function (v) { var args = arguments; return v.apply( - context, + context, map(function (s) {return s(args);}, nofnodes)); - }); + }); } else if (fn instanceof Function) { return createTimeSyncNode(nodes).lift_e( function (arr) { @@ -795,13 +795,13 @@ function flapjaxInit(options) { return createTimeSyncNode(nodes).lift_e( function (arr) { return arr[0].apply( - this, + this, map(function (s) {return s(arr); }, nofnodes)); }); } else {throw 'unknown lift_e case';} }; fxExport(core,lift_e,'lift_e','transform_e','map_e','apply_e'); - + EventStream.prototype.snapshot_e = function (valueB) { return createNode( [this], @@ -809,7 +809,7 @@ function flapjaxInit(options) { p.value = valueNow(valueB); s(p); } - ); + ); }; fxMethodSynonyms(EventStream,'snapshot_e','snapshot','takeSnapshot'); @@ -821,7 +821,7 @@ function flapjaxInit(options) { EventStream.prototype.filterRepeats_e = function(optStart) { var hadFirst = optStart === undefined ? false : true; var prev = optStart; - + return this.filter_e(function (v) { if (!hadFirst || !(isEqual(prev,v))) { hadFirst = true; @@ -854,7 +854,7 @@ function flapjaxInit(options) { }()); return out; }; - + //calm_e: Event a * [Behaviour] Number -> Event a EventStream.prototype.calm_e = function(time) { if (time instanceof Behaviour) { @@ -865,26 +865,26 @@ function flapjaxInit(options) { var towards = null; return function (s, p) { if (towards !== null) { clearTimeout(towards); } - towards = setTimeout( function () { towards = null; sendEvent(out,p.value) }, valueNow(time)); + towards = setTimeout( function () { towards = null; sendEvent(out,p.value);}, valueNow(time)); }; }()); return out; } else { - return calmStatic_e(this,time); + return calmStatic_e(this,time); } }; fxMethodSynonyms(EventStream,'calm_e','calm'); - + var calm_e = function(sourceE,interval) { return sourceE.calm_e(interval); }; fxExport(core,calm_e,'calm_e'); - + EventStream.prototype.blind_e = function (time) { return createNode( [this], function () { - var intervalFn = + var intervalFn = time instanceof Behaviour? function () { return valueNow(time); } : function () { return time; }; @@ -899,12 +899,12 @@ function flapjaxInit(options) { }()); }; fxMethodSynonyms(EventStream,'blind_e','blind'); - + var blind_e = function(sourceE,interval) { return sourceE.blind_e(interval); }; fxExport(core,blind_e,'blind_e'); - + EventStream.prototype.hold = function(init) { return new Behaviour(this,init); }; @@ -914,10 +914,10 @@ function flapjaxInit(options) { if (!(e instanceof EventStream)) { throw 'hold: expected EventStream; received ' + e; } - return e.hold(init); + return e.hold(init); }; fxExport(core,hold,'hold'); - + Behaviour.prototype.valueNow = function() { return this.last; }; @@ -928,20 +928,20 @@ function flapjaxInit(options) { return this.underlying; }; fxMethodSynonyms(Behaviour,'changes','toEvent'); - - var changes = function (behave) { return behave.changes(); } + + var changes = function (behave) { return behave.changes(); }; fxExport(core,changes,'changes'); - + Behaviour.prototype.switch_b = function() { var behaviourCreatorsB = this; var init = valueNow(behaviourCreatorsB); - + var prevSourceE = null; - + var receiverE = new internal_e(); - + //XXX could result in out-of-order propagation! Fix! - var makerE = + var makerE = createNode( [changes(behaviourCreatorsB)], function (_, p) { @@ -949,67 +949,67 @@ function flapjaxInit(options) { if (prevSourceE != null) { removeListener(prevSourceE, receiverE); } - + prevSourceE = changes(p.value); attachListener(prevSourceE, receiverE); - + sendEvent(receiverE, valueNow(p.value)); }); - + if (init instanceof Behaviour) { sendEvent(makerE, init); } - + return hold( receiverE, init instanceof Behaviour? valueNow(init) : init); }; fxMethodSynonyms(Behaviour,'switch_b','forwardLatest'); - + var switch_b = function (b) { return b.switch_b(); }; fxExport(core,switch_b,'switch_b'); - + //TODO test, signature var timer_b = function(interval) { return hold(timer_e(interval), (new Date()).getTime()); }; fxExport(dom,timer_b,'timer_b','asTimer_b'); - + //TODO test, signature var delayStatic_b = function (triggerB, time, init) { return hold(delayStatic_e(changes(triggerB), time), init); }; - + //TODO test, signature Behaviour.prototype.delay_b = function (time, init) { var triggerB = this; if (time instanceof Behaviour) { return hold( delay_e( - changes(triggerB), + changes(triggerB), time), arguments.length > 3 ? init : valueNow(triggerB)); } else { return delayStatic_b( - triggerB, + triggerB, time, arguments.length > 3 ? init : valueNow(triggerB)); } }; fxMethodSynonyms(Behaviour,'delay_b','delay'); - - var delay_b = function(srcB, timeB, init) { - return srcB.delay_b(timeB,init); + + var delay_b = function(srcB, timeB, init) { + return srcB.delay_b(timeB,init); }; fxExport(core,delay_b,'delay_b'); - + //artificially send a pulse to underlying event node of a behaviour //note: in use, might want to use a receiver node as a proxy or an identity map Behaviour.prototype.sendBehaviour = function(val) { sendEvent(this.underlyingRaw,val); }; Behaviour.prototype.sendBehavior = Behaviour.prototype.sendBehaviour; - + var sendBehaviour = function (b,v) { b.sendBehaviour(v); }; fxExport(core,sendBehaviour,'sendBehaviour'); fxExport(core,sendBehaviour,'sendBehavior'); @@ -1022,14 +1022,14 @@ function flapjaxInit(options) { return lift_b(function(te,t,f) { return te ? t : f; },testB,trueB,falseB); }; fxMethodSynonyms(Behaviour,'if_b','choose_b','choose'); - + var if_b = function(test,cons,altr) { if (!(test instanceof Behaviour)) { test = constant_b(test); }; - + return test.if_b(cons,altr); }; fxExport(core,if_b,'if_b','choose_b'); - + //cond_b: . [Behaviour boolean, Behaviour a] -> Behaviour a var cond_b = function (/* . pairs */ ) { @@ -1042,14 +1042,14 @@ function flapjaxInit(options) { }].concat(map(function(pair) {return pair[0];},pairs).concat(map(function(pair) {return pair[1];},pairs)))); }; fxExport(core,cond_b,'cond_b'); - + //TODO optionally append to objects //createConstantB: a -> Behaviour a var constant_b = function (val) { return new Behaviour(internal_e(), val); }; fxExport(core,constant_b,'constant_b','receiver_b'); - + var lift_b = function (fn /* . behaves */) { var args = slice(arguments, 1); @@ -1058,21 +1058,21 @@ function flapjaxInit(options) { map(changes, filter(function (v) { return v instanceof Behaviour; }, arguments)); - + //calculate new vals var getCur = function (v) { return v instanceof Behaviour ? v.last : v; }; - + var ctx = this; var getRes = function () { return getCur(fn).apply(ctx, map(getCur, args)); }; - + if(constituentsE.length == 1) { return new Behaviour(constituentsE[0],getRes(),getRes); } - + //gen/send vals @ appropriate time var prevStamp = -1; var mid = createNode(constituentsE, function (s, p) { @@ -1083,14 +1083,14 @@ function flapjaxInit(options) { return new Behaviour(mid,getRes(),getRes); }; fxExport(core,lift_b,'lift_b','transform_b','apply_b'); - + Behaviour.prototype.lift_b = function(/* args */) { var args= slice(arguments,0).concat([this]); return lift_b.apply(this,args); }; fxMethodSynonyms(Behaviour,'lift_b','transform_b','apply_b','transform', 'lift'); - + var and_b = function (/* . behaves */) { return lift_b.apply({},[function() { for(var i=0; i<arguments.length; i++) {if(!arguments[i]) return false;} @@ -1098,12 +1098,12 @@ function flapjaxInit(options) { }].concat(slice(arguments,0))); }; fxExport(core, and_b, 'and_b'); - + Behaviour.prototype.and_b = function() { return and_b([this].concat(arguments)); }; fxMethodSynonyms(Behaviour,'and_b','and'); - + var or_b = function (/* . behaves */ ) { return lift_b.apply({},[function() { for(var i=0; i<arguments.length; i++) {if(arguments[i]) return true;} @@ -1111,64 +1111,64 @@ function flapjaxInit(options) { }].concat(slice(arguments,0))); }; fxExport(core,or_b,'or_b'); - + Behaviour.prototype.or_b = function () { return or_b([this].concat(arguments)); }; fxMethodSynonyms(Behaviour, 'or_b', 'or'); - + Behaviour.prototype.not_b = function() { return this.lift_b(function(v) { return !v; }); }; fxMethodSynonyms(Behaviour,'not_b','not'); - + var not_b = function(b) { return b.not_b(); }; fxExport(core,not_b,'not_b'); - + Behaviour.prototype.blind_b = function (intervalB) { return changes(this).blind_e(intervalB).hold(this.valueNow()); }; fxMethodSynonyms(Behaviour,'blind_b','blind'); - + var blind_b = function(srcB,intervalB) { return srcB.blind_b(intervalB); }; fxExport(core,blind_b,'blind_b'); - + Behaviour.prototype.calm_b = function (intervalB) { return this.changes().calm_e(intervalB).hold(this.valueNow()); }; fxMethodSynonyms(Behaviour,'calm_b','calm'); - - var calm_b = function (srcB,intervalB) { + + var calm_b = function (srcB,intervalB) { return srcB.calm_b(intervalB); }; fxExport(core,calm_b,'calm_b'); - + ////////////////////////////////////////////////////////////////////////////////////////////////////////////////////// // DOM Utilities - + //credit Scott Andrew //usage: addEvent(myDomObj, "mouseover", event->void ) //warning: do not use 'this' as meaning depends on browser (myDomObj vs window) //addEvent: Dom * String DomEventEnum * (DomEvent -> a) -> Void var addEvent = function (obj, evType, fn) { //TODO encode mouseleave evt, formalize new evt interface - + if (obj.addEventListener) { obj.addEventListener(evType, fn, false); //TODO true fails on Opera return true; } else if (obj.attachEvent) { //some reason original had code bloat here - return obj.attachEvent("on"+evType, fn); + return obj.attachEvent("on"+evType, fn); } else { - return false; + return false; } }; fxExport(domMisc,addEvent,'addEvent'); - // The Flapjax library does not use this function - //credit Dustin Diaz + // The Flapjax library does not use this function + //credit Dustin Diaz //note: node/tag optional //getElementsByClass: Regexp CSSSelector * Dom * String DomNodeEnum -> Array Dom var getElementsByClass = function (searchClass, node, tag) { @@ -1186,22 +1186,22 @@ function flapjaxInit(options) { return classElements; }; fxExport(domMisc,getElementsByClass,'getElementsByClass','$$'); - + //assumes IDs already preserved //swapDom: (Dom a U String) [* (Dom b U String)] -> Dom a var swapDom = function(replaceMe, withMe) { if ((replaceMe === null) || (replaceMe === undefined)) { throw ('swapDom: expected dom node or id, received: ' + replaceMe); } //SAFETY - + var replaceMeD = getObj(replaceMe); if (!(replaceMeD.nodeType > 0)) { throw ('swapDom expected a Dom node as first arg, received ' + replaceMeD); } //SAFETY - + if (withMe) { var withMeD = getObj(withMe); if (!(withMeD.nodeType > 0)) { throw 'swapDom: can only swap with a DOM object'; } //SAFETY try { if(withMeD != replaceMeD) replaceMeD.parentNode.replaceChild(withMeD, replaceMeD); } catch (e) { - throw('swapDom error in replace call: withMeD: ' + withMeD + ', replaceMe Parent: ' + replaceMeD + ', ' + e + ', parent: ' + replaceMeD.parentNode); + throw('swapDom error in replace call: withMeD: ' + withMeD + ', replaceMe Parent: ' + replaceMeD + ', ' + e + ', parent: ' + replaceMeD.parentNode); } } else { replaceMeD.parentNode.removeChild(replaceMeD); //TODO isolate child and set innerHTML to "" to avoid psuedo-leaks? @@ -1209,9 +1209,9 @@ function flapjaxInit(options) { return replaceMeD; }; fxExport(domMisc,swapDom,'swapDom'); - + //getObj: String U Dom -> Dom - //throws + //throws // 'getObj: expects a Dom obj or Dom id as first arg' // 'getObj: flapjax: cannot access object' // 'getObj: no obj to get @@ -1222,21 +1222,21 @@ function flapjaxInit(options) { else if ((typeof(name) == 'null') || (typeof(name) == 'undefined')) { throw 'getObj: expects a Dom obj or Dom id as first arg'; } else { - - var res = + + var res = document.getElementById ? document.getElementById(name) : document.all ? document.all[name] : document.layers ? document.layers[name] : (function(){ throw 'getObj: flapjax: cannot access object';})(); - if ((res === null) || (res === undefined)) { - throw ('getObj: no obj to get: ' + name); + if ((res === null) || (res === undefined)) { + throw ('getObj: no obj to get: ' + name); } return res; } }; fxExport(domMisc,getObj,'getObj'); fxExport(domMisc,getObj,'$'); - + //helper to reduce obj look ups //getDynObj: domNode . Array (id) -> domObj //obj * [] -> obj @@ -1251,9 +1251,9 @@ function flapjaxInit(options) { acc = acc[indices[i]]; } return acc; - } + } }; - + var getDomVal = function (domObj, indices) { var val = getMostDom(domObj, indices); if (indices && indices.length > 0) { @@ -1261,24 +1261,24 @@ function flapjaxInit(options) { } return val; }; - + //TODO: manual timer management stinks. // TODO: Name turn off or somethin var ___timerID = 0; - var __getTimerId = function () { return ++___timerID; }; + var __getTimerId = function () { return ++___timerID; }; var timerDisablers = []; - + var disableTimerNode = function (node) { timerDisablers[node.__timerId](); }; - + var disableTimer = function (v) { - if (v instanceof Behaviour) { - disableTimerNode(v.underlyingRaw); + if (v instanceof Behaviour) { + disableTimerNode(v.underlyingRaw); } else if (v instanceof EventStream) { disableTimerNode(v); } }; fxExport(dom,disableTimer,'disableTimer'); - + var createTimerNodeStatic = function (interval) { var node = internal_e(); node.__timerId = __getTimerId(); @@ -1287,35 +1287,35 @@ function flapjaxInit(options) { timerDisablers[node.__timerId] = function () {clearInterval(timer); }; return node; }; - + var timer_e = function (interval) { if (interval instanceof Behaviour) { var receiverE = internal_e(); - + //the return var res = receiverE.switch_e(); - + //keep track of previous timer to disable it var prevE = createTimerNodeStatic(valueNow(interval)); - + //init sendEvent(receiverE, prevE); - + //interval changes: collect old timer createNode( [changes(interval)], function (_, p) { - disableTimerNode(prevE); + disableTimerNode(prevE); prevE = createTimerNodeStatic(p.value); sendEvent(receiverE, prevE); }); - + res.__timerId = __getTimerId(); timerDisablers[res.__timerId] = function () { disableTimerNode[prevE](); return; }; - + return res; } else { return createTimerNodeStatic(interval); @@ -1348,18 +1348,18 @@ function flapjaxInit(options) { // Array [[Behaviour] Object *] [[Behaviour] Array] [Behaviour] Dom U String U undefined // --> {attribs: Array [Behaviour] Object, arrs: Array [Behaviour] Array [Behaviour] Dom } // split an arguments array into: - // 1. arrs: (coalesced, and possibly time varying) arrays of dom objects + // 1. arrs: (coalesced, and possibly time varying) arrays of dom objects // 2. attribs: attribute objects extractParameters: function(args) { this.arrs = []; var attribs = []; - + var curarr = []; this.arrs.push(curarr); for (var i = 0; i < args.length; i++) { if (args[i] instanceof Behaviour) { var vn = valueNow(args[i]); - if (vn instanceof Array) { + if (vn instanceof Array) { this.arrs.push(args[i]); curarr = []; this.arrs.push(curarr); @@ -1392,26 +1392,26 @@ function flapjaxInit(options) { }, insertChildrenNodes: function() { var ctx = this; - - function quickNode(e) { + + function quickNode(e) { if ((typeof(e) == 'object') && (e.nodeType)) - return e; + return e; else if ( e == undefined ) - return document.createTextNode(''); - else - return document.createTextNode(e); + return document.createTextNode(''); + else + return document.createTextNode(e); } - + function unBehaviourize(arr) { return map(function(n) {return (n instanceof Behaviour) ? valueNow(n) : n;},arr) } - + var lnodes = map(function() {return [];},this.arrs); var arrLastVals = map(unBehaviourize,unBehaviourize(this.arrs)); - + var arrChangesE = internal_e(); var nodeChangesE = internal_e(); - + function attachNodes(i,arr) { for(var j=0;j<arr.length;j++) { var cnode = arr[j]; @@ -1425,7 +1425,7 @@ function flapjaxInit(options) { } } } - + var childChangesE = merge_e( // Behaviour arrays change arrChangesE.lift_e(function(ai) { @@ -1461,7 +1461,7 @@ function flapjaxInit(options) { return ctx.currentTag; })); childChangesE.lift_e(function(cc) {sendEvent(ctx.resE,cc);}); - + for(var i=0; i<this.arrs.length;i++) { for(var j=0; j<arrLastVals[i].length; j++) { arrLastVals[i][j] = quickNode(arrLastVals[i][j]); @@ -1491,7 +1491,7 @@ function flapjaxInit(options) { this.enstyleProperty(obj,valsV, i); } } - } + } else { throw 'enstyle: expected object literals'; } //SAFETY }, enstyleProperty: function (obj, vals, i) { @@ -1513,11 +1513,11 @@ function flapjaxInit(options) { } } }; - + d.createParameterizedTagB = function(tagName) { return new d.TagB(tagName,slice(arguments,1)).resB; - } - + }; + d.enstyleStaticProperty = function (obj, props, index) { if (typeof(props[index]) == 'object') { for (var i in props[index]) { @@ -1531,16 +1531,16 @@ function flapjaxInit(options) { if (index == 'selected') obj['defaultSelected'] = props[index]; /* TODO: this should maybe be elsewhere? */ } }; - + d.staticTagMaker = function (tagName) { - + return function () { - + var tagD = document.createElement(tagName); if (!(tagD.nodeType > 0)) { throw (tagName + ': invalid tag name'); } //SAFETY - + //partition input - + // if (arguments[1] === null || arguments[1] === undefined) { arguments[1] = {}; } var attribs = []; for (var i = 0; i < arguments.length; i++) { @@ -1556,91 +1556,91 @@ function flapjaxInit(options) { } } else if (!arguments[i]) { //ignore - } else if ((typeof(arguments[i]) == 'object') && + } else if ((typeof(arguments[i]) == 'object') && (arguments[i].nodeType > 0)) { tagD.appendChild(arguments[i]); } else if (typeof(arguments[i]) == 'object') { attribs.push(arguments[i]); } else { - tagD.appendChild(document.createTextNode(arguments[i])); + tagD.appendChild(document.createTextNode(arguments[i])); } } - - if (attribs.length == 1) { + + if (attribs.length == 1) { for (var k in attribs[0]) { if (!(Object.prototype) || !(Object.prototype[k])) { - d.enstyleStaticProperty(tagD, attribs[0], k); + d.enstyleStaticProperty(tagD, attribs[0], k); } } - } else if (attribs.length > 0) { + } else if (attribs.length > 0) { throw 'static enstyle: expected object literals'; //SAFETY } /* else { alert('no attribs on: ' + tagName); } */ - - + + return tagD; }; }; - - - - var generatedTags = - [ "a", "b", "blockquote", "br", "button", "canvas", "div", "fieldset", - "form", "font", "h1", "h2", "h3", "h4", "hr", "img", "iframe", "input", - "label", "legend", "li", "ol", "optgroup", "option", - "p", "pre", "select", "span", "strong", "table", "tbody", + + + + var generatedTags = + [ "a", "b", "blockquote", "br", "button", "canvas", "div", "fieldset", + "form", "font", "h1", "h2", "h3", "h4", "hr", "img", "iframe", "input", + "label", "legend", "li", "ol", "optgroup", "option", + "p", "pre", "select", "span", "strong", "table", "tbody", "td", "textarea", "tfoot", "th", "thead", "tr", "tt", "ul" ]; - + map( - function (tagName) { - + function (tagName) { + var upper = tagName.toUpperCase(); - + //d.<TAG>B - d[upper + 'B'] = function () { + d[upper + 'B'] = function () { return d.createParameterizedTagB.apply(this, [tagName].concat(slice(arguments,0))); - }; + }; annotate(d[upper+'B'],[upper+'B']); - + //d.<TAG> d[upper] = d.staticTagMaker(tagName); //faster, simple /* function () { // 8/16/06 - leo - arguments bug // more forgiving: allows reactive children (just doesn't propagate them) - var args = [b.maybeEmpty].concat(slice(arguments, 0)); + var args = [b.maybeEmpty].concat(slice(arguments, 0)); return valueNow(d[upper + 'B'].apply(this, args)); }; */ annotate(d[upper],[upper]); }, generatedTags); - - //TEXTB: Behaviour a -> Behaviour Dom TextNode + + //TEXTB: Behaviour a -> Behaviour Dom TextNode d.TEXTB = function (strB) { // if (!(strB instanceof Behaviour || typeof(strB) == 'string')) { throw 'TEXTB: expected Behaviour as second arg'; } //SAFETY if (!(strB instanceof Behaviour)) { strB = constant_b(strB); } - + return hold( changes(strB).lift_e( function (txt) { return document.createTextNode(txt); }), document.createTextNode(valueNow(strB))); }; annotate(d.TEXTB,['TEXTB']); - + var TEXT = function (str) { return document.createTextNode(str); }; fxExport(dom,TEXT,'TEXT'); - + ////////////////////////////////////////////////////////////////////////////////////////////////////////////////////// // Reactive DOM - - //tagRec: Array (EventName a) * + + //tagRec: Array (EventName a) * // ( .Array (Event a) * Array (Event a) -> Behaviour Dom) -> Behaviour Dom var tagRec = function (eventNames, maker) { if (!(eventNames instanceof Array)) { throw 'tagRec: expected array of event names as first arg'; } //SAFETY if (!(maker instanceof Function)) { throw 'tagRec: expected function as second arg'; } //SAFETY - + var numEvents = eventNames.length; var internals = [ ]; var switches = [ ]; @@ -1648,33 +1648,33 @@ function flapjaxInit(options) { internals[i] = internal_e(); switches[i] = internals[i].switch_e(); }; - + var domB = maker.apply(this,switches); - + var prevValue; - + var interceptE = createNode([domB.changes()],function (_,p) { if (isEqual(p.value,prevValue)) { return; } - + prevValue = p.value; for (var i = 0; i < numEvents; i++) { sendEvent(internals[i],extractEvent_e(prevValue,eventNames[i])); }; }); - + sendEvent(interceptE,domB.valueNow()); - + return domB; }; fxExport(dom,tagRec,'tagRec','nodeWithOwnEvents'); - + //extractEventStatic_e: Dom * String -> Event var extractEventStatic_e = function (domObj, eventName) { if (!eventName) { throw 'extractEvent_e : no event name specified'; } if (!domObj) { throw 'extractEvent_e : no DOM element specified'; } - + domObj = getObj(domObj); - + var primEventE = internal_e(); addEvent(domObj,eventName,function(evt) { sendEvent(primEventE, evt || window.event); @@ -1682,7 +1682,7 @@ function flapjaxInit(options) { // checking. return true; }); - + return primEventE; }; @@ -1693,47 +1693,47 @@ function flapjaxInit(options) { } else { var domE = domB.changes(); - + var eventEE = domE.lift_e(function(dom) { return extractEventStatic_e(dom,eventName); }); - + var resultE = eventEE.switch_e(); - + sendEvent(domE,domB.valueNow()); - + return resultE; }; }; fxExport(dom,extractEvent_e,'extractEvent_e','$EVT'); - - //extractEvents_e: - // [Behaviour] Dom + + //extractEvents_e: + // [Behaviour] Dom // . Array String // -> Event // ex: extractEvents_e(m, 'body', 'mouseover', 'mouseout') d.extractEvents_e = function (domObj /* . eventNames */) { var eventNames = slice(arguments, 1); - + var events = map( function (eventName) { - return extractEvent_e(domObj, eventName); + return extractEvent_e(domObj, eventName); }, eventNames.length === 0 ? [] : eventNames); - + return merge_e.apply(this, events); }; annotate(d.extractEvents_e,['extractEvents_e'],0,[Behaviour.prototype],['extractEvents_e']); - + //value of dom form object during trigger d.extractValueOnEvent_e = function (triggerE, domObj) { if (!(triggerE instanceof EventStream)) { throw 'extractValueOnEvent_e: expected Event as first arg'; } //SAFETY - + return changes(d.extractValueOnEvent_b.apply(this, arguments)); - + }; annotate(d.extractValueOnEvent_e,['extractValueOnEvent_e']); - + //extractDomFieldOnEvent_e: Event * Dom U String . Array String -> Event a d.extractDomFieldOnEvent_e = function (triggerE, domObj /* . indices */) { if (!(triggerE instanceof EventStream)) { throw 'extractDomFieldOnEvent_e: expected Event as first arg'; } //SAFETY @@ -1743,23 +1743,23 @@ function flapjaxInit(options) { function () { return getDomVal(domObj, indices); }); return res; }; - + d.extractValue_e = function (domObj) { return changes(d.extractValue_b.apply(this, arguments)); }; annotate(d.extractValue_e,['extractValue_e','$E']); - + //extractValueOnEvent_b: Event * DOM -> Behaviour // value of a dom form object, polled during trigger d.extractValueOnEvent_b = function (triggerE, domObj) { return d.extractValueStatic_b(domObj, triggerE); }; annotate(d.extractValueOnEvent_b,['extractValueOnEvent_b']); - + //extractValueStatic_b: DOM [ * Event ] -> Behaviour a //If no trigger for extraction is specified, guess one d.extractValueStatic_b = function (domObj, triggerE) { - + var objD; try { objD = getObj(domObj); @@ -1770,36 +1770,36 @@ function flapjaxInit(options) { } catch (e) { objD = {type: 'radio-group', name: domObj}; } - + var getter; // get value at any current point in time - - + + switch (objD.type) { - + //TODO: checkbox.value instead of status? - case 'checkbox': - + case 'checkbox': + return hold( filterRepeats_e( d.extractDomFieldOnEvent_e( - triggerE ? triggerE : + triggerE ? triggerE : d.extractEvents_e( - objD, + objD, 'click', 'keyup', 'change'), objD, 'checked'),objD.checked), objD.checked); - + case 'select-one': - - getter = function (_) { - return objD.selectedIndex > -1 ? + + getter = function (_) { + return objD.selectedIndex > -1 ? (objD.options[objD.selectedIndex].value ? objD.options[objD.selectedIndex].value : objD.options[objD.selectedIndex].innerText) : undefined; }; - + return hold( filterRepeats_e( (triggerE ? triggerE : @@ -1807,10 +1807,10 @@ function flapjaxInit(options) { objD, 'click', 'keyup', 'change')).lift_e(getter)),getter(), getter()); - + case 'select-multiple': //TODO ryan's cfilter adapted for equality check - + getter = function (_) { var res = []; for (var i = 0; i < objD.options.length; i++) { @@ -1820,95 +1820,95 @@ function flapjaxInit(options) { } return res; }; - - + + return hold( - (triggerE ? triggerE : + (triggerE ? triggerE : d.extractEvents_e( objD, 'click', 'keyup', 'change')).lift_e(getter), getter()); - + case 'text': case 'textarea': case 'hidden': case 'password': - + return hold( filterRepeats_e( d.extractDomFieldOnEvent_e( triggerE ? triggerE : d.extractEvents_e( - objD, + objD, 'click', 'keyup', 'change'), objD, 'value'),objD.value), objD.value); - + case 'button': //same as above, but don't filter repeats - + return hold( d.extractDomFieldOnEvent_e( triggerE ? triggerE : d.extractEvents_e( - objD, + objD, 'click', 'keyup', 'change'), objD, 'value'), objD.value); - - - case 'radio': + + + case 'radio': case 'radio-group': - + //TODO returns value of selected button, but if none specified, // returns 'on', which is ambiguous. could return index, // but that is probably more annoying - + var radiosAD = filter( - function (elt) { + function (elt) { return (elt.type == 'radio') && - (elt.getAttribute('name') == objD.name); + (elt.getAttribute('name') == objD.name); }, document.getElementsByTagName('input')); - - getter = + + getter = objD.type == 'radio' ? - + function (_) { return objD.checked; } : - + function (_) { for (var i = 0; i < radiosAD.length; i++) { if (radiosAD[i].checked) { - return radiosAD[i].value; + return radiosAD[i].value; } } - return undefined; //TODO throw exn? + return undefined; //TODO throw exn? }; - + var actualTriggerE = triggerE ? triggerE : merge_e.apply( this, map( - function (radio) { + function (radio) { return d.extractEvents_e( - radio, + radio, 'click', 'keyup', 'change'); }, radiosAD)); - + return hold( filterRepeats_e( actualTriggerE.lift_e(getter),getter()), getter()); - + default: - + throw ('extractValueStatic_b: unknown value type "' + objD.type + '"'); } }; - + d.extractValue_b = function (domObj) { if (domObj instanceof Behaviour) { return lift_b(function (dom) { return d.extractValueStatic_b(dom); }, @@ -1919,7 +1919,7 @@ function flapjaxInit(options) { } }; annotate(d.extractValue_b,['extractValue_b','$B'],0,[Behaviour.prototype],['extractValue_b','$B']); - + //into[index] = deepValueNow(from) via descending from object and mutating each field d.deepStaticUpdate = function (into, from, index) { var fV = (from instanceof Behaviour)? valueNow(from) : from; @@ -1934,7 +1934,7 @@ function flapjaxInit(options) { into[index] = fV; } }; - + //note: no object may be time varying, just the fields //into[index] = from //only updates on changes @@ -1954,7 +1954,7 @@ function flapjaxInit(options) { createNode( [changes(from)], function (s, p) { - if (index) { + if (index) { var old = into[index]; into[index] = p.value; } @@ -1963,70 +1963,70 @@ function flapjaxInit(options) { } } }; - - + + d.insertValue = function (val, domObj /* . indices */) { var indices = slice(arguments, 2); var parent = getMostDom(domObj, indices); - d.deepStaticUpdate(parent, val, indices ? indices[indices.length - 1] : undefined); + d.deepStaticUpdate(parent, val, indices ? indices[indices.length - 1] : undefined); }; annotate(d.insertValue,['insertValue']); - - //TODO convenience method (default to firstChild nodeValue) + + //TODO convenience method (default to firstChild nodeValue) d.insertValueE = function (triggerE, domObj /* . indices */) { if (!(triggerE instanceof EventStream)) { throw 'insertValueE: expected Event as first arg'; } //SAFETY - + var indices = slice(arguments, 2); var parent = getMostDom(domObj, indices); - + triggerE.lift_e(function (v) { d.deepStaticUpdate(parent, v, indices? indices[indices.length - 1] : undefined); }); }; annotate(d.insertValueE,['insertValueE'],0,[EventStream.prototype],['insertValueE']); - + //insertValueB: Behaviour * domeNode . Array (id) -> void //TODO notify adapter of initial state change? - d.insertValueB = function (triggerB, domObj /* . indices */) { - + d.insertValueB = function (triggerB, domObj /* . indices */) { + var indices = slice(arguments, 2); var parent = getMostDom(domObj, indices); - - + + //NOW d.deepStaticUpdate(parent, triggerB, indices ? indices[indices.length - 1] : undefined); - + //LATER d.deepDynamicUpdate(parent, triggerB, indices? indices[indices.length -1] : undefined); - + }; annotate(d.insertValueB,['insertValueB'],0,[Behaviour.prototype],['insertValueB']); - + //TODO copy dom event call backs of original to new? i don't thinks so // complication though: registration of call backs should be scoped d.insertDomE = function (triggerE, domObj) { - + if (!(triggerE instanceof EventStream)) { throw 'insertDomE: expected Event as first arg'; } //SAFETY - + var objD = getObj(domObj); - + var res = triggerE.lift_e( function (newObj) { //TODO safer check - if (!((typeof(newObj) == 'object') && (newObj.nodeType == 1))) { + if (!((typeof(newObj) == 'object') && (newObj.nodeType == 1))) { newObj = d.SPAN({}, newObj); } swapDom(objD, newObj); objD = newObj; return newObj; // newObj; }); - + return res; }; annotate(d.insertDomE,['insertDomE'],0,[EventStream.prototype],['insertDomE']); - - //insertDom: dom - // * dom + + //insertDom: dom + // * dom // [* (null | undefined | 'over' | 'before' | 'after' | 'leftMost' | 'rightMost' | 'beginning' | 'end'] // -> void // TODO: for consistency, switch replaceWithD, hookD argument order @@ -2038,7 +2038,7 @@ function flapjaxInit(options) { case 'over': swapDom(hookD,replaceWithD); break; - case 'before': + case 'before': hookD.parentNode.insertBefore(replaceWithD, hookD); break; case 'after': @@ -2049,9 +2049,9 @@ function flapjaxInit(options) { } break; case 'leftMost': - if (hookD.parentNode.firstChild) { + if (hookD.parentNode.firstChild) { hookD.parentNode.insertBefore( - replaceWithD, + replaceWithD, hookD.parentNode.firstChild); } else { hookD.parentNode.appendChild(replaceWithD); } break; @@ -2059,9 +2059,9 @@ function flapjaxInit(options) { hookD.parentNode.appendChild(replaceWithD); break; case 'beginning': - if (hookD.firstChild) { + if (hookD.firstChild) { hookD.insertBefore( - replaceWithD, + replaceWithD, hookD.firstChild); } else { hookD.appendChild(replaceWithD); } break; @@ -2072,39 +2072,39 @@ function flapjaxInit(options) { throw ('domInsert: unknown position: ' + optPosition); } }; - - //insertDom: dom - // * dom U String domID + + //insertDom: dom + // * dom U String domID // [* (null | undefined | 'over' | 'before' | 'after' | 'leftMost' | 'rightMost' | 'beginning' | 'end'] // -> void d.insertDomClean = function (replaceWithD, hook, optPosition) { //TODO span of textnode instead of textnode? d.insertDom( - getObj(hook), + getObj(hook), ((typeof(replaceWithD) == 'object') && (replaceWithD.nodeType > 0)) ? replaceWithD : - document.createTextNode(replaceWithD), - optPosition); + document.createTextNode(replaceWithD), + optPosition); }; annotate(d.insertDomClean,['insertDom']); - + //TODO test - //insertDomB: - // [Behaviour] String U Dom - // [* ( id U null U undefined ) + //insertDomB: + // [Behaviour] String U Dom + // [* ( id U null U undefined ) // [* ('before' U 'after' U 'leftMost' U 'rightMost' U 'over' U 'beginning' U 'end')]] // -> Behaviour a //if optID not specified, id must be set in init val of trigger //if position is not specified, default to 'over' - //performs initial swap onload + //performs initial swap onload d.insertDomB = function (initTriggerB, optID, optPosition) { - - if (!(initTriggerB instanceof Behaviour)) { + + if (!(initTriggerB instanceof Behaviour)) { initTriggerB = constant_b(initTriggerB); } - - var triggerB = + + var triggerB = lift_b( - function (d) { + function (d) { if ((typeof(d) == 'object') && (d.nodeType > 0)) { return d; } else { @@ -2114,26 +2114,26 @@ function flapjaxInit(options) { } }, initTriggerB); - + var initD = valueNow(triggerB); - if (!((typeof(initD) == 'object') && (initD.nodeType == 1))) { throw ('insertDomB: initial value conversion failed: ' + initD); } //SAFETY - + if (!((typeof(initD) == 'object') && (initD.nodeType == 1))) { throw ('insertDomB: initial value conversion failed: ' + initD); } //SAFETY + d.insertDom( - optID === null || optID === undefined ? getObj(initD.getAttribute('id')) : getObj(optID), - initD, + optID === null || optID === undefined ? getObj(initD.getAttribute('id')) : getObj(optID), + initD, optPosition); - + var resB = hold( d.insertDomE( changes(triggerB), - initD), + initD), initD); - + return resB; }; annotate(d.insertDomB,['insertDomB'],0,[Behaviour.prototype],['insertDomB']); - - + + d.extractId_b = function (id, start) { return hold( @@ -2146,7 +2146,7 @@ function flapjaxInit(options) { getObj(id)); }; annotate(d.insertDomB,['extractId_b'],1,[Behaviour.prototype],['extractId_b']); - + var mouse_e = function(elem) { return extractEvent_e(elem,'mousemove') .lift_e(function(evt) { @@ -2162,32 +2162,32 @@ function flapjaxInit(options) { } }); }; - + var mouse_b = function(elem) { return mouse_e(elem).hold({ left: 0, top: 0 }); } fxExport(dom,mouse_b,'mouse_b'); - + var mouseLeft_b = function(elem) { return lift_b(function(v) { return v.left; },mouse_b(elem)); }; fxExport(dom,mouseLeft_b,'mouseLeft_b'); - + var mouseTop_b = function(elem) { return mouse_b(elem).lift_b(function(v) { return v.top; }); }; - + fxExport(dom,mouseTop_b,'mouseTop_b'); - + var clicks_e = function(elem) { return extractEvent_e(elem,'click'); }; fxExport(dom,clicks_e,'clicks_e'); - + ////////////////////////////////////////////////////////////////////////////// // Combinators for web services - - + + //credit Matt White var getURLParam = function (param) { var lparam = param.toLowerCase(); @@ -2207,7 +2207,7 @@ function flapjaxInit(options) { else return aReturn; }; fxExport(domMisc,getURLParam,'getURLParam','$URL'); - + //credit Quirksmode //readCookie: String -> String U Undefined var readCookie = function (name) { @@ -2216,21 +2216,21 @@ function flapjaxInit(options) { for (var i=0; i < ca.length; i++) { var co = ca[i]; while (co.charAt(0) == ' ') { co = co.substring(1, co.length); } - if (co.indexOf(nameEQ) === 0) { + if (co.indexOf(nameEQ) === 0) { return co.substring(nameEQ.length, co.length); } } - return undefined; + return undefined; }; fxExport(domMisc,readCookie,'readCookie'); - + //========== dynamic scripts ========== var scriptCounter = 0; var deleteScript = function (scriptID) { var scriptD = getObj(scriptID); scriptD.parentNode.removeChild(scriptD); //TODO isolate child and set innerHTML to "" to avoid psuedo-leaks? }; - + // optional fn/param that gets polled until parm is defined var runScript = function (url, fn, param) { var script = document.createElement("script"); @@ -2239,7 +2239,7 @@ function flapjaxInit(options) { script.setAttribute('id', scriptID); document.getElementsByTagName("head").item(0).appendChild(script); var timer = {}; - var check = + var check = function () { eval("try { if (" + param + "!== undefined) {var stat = " + param + ";}} catch (e) {}"); if (stat !== undefined) { @@ -2247,35 +2247,35 @@ function flapjaxInit(options) { clearInterval(timer.timer); clearInterval(timer.timeout); if (fn instanceof Function) { - fn(stat); + fn(stat); } deleteScript(scriptID); } }; timer.timer = setInterval(check, 3500); - timer.timeout = - setTimeout( - function () { + timer.timeout = + setTimeout( + function () { try { clearInterval(timer.timer); } catch (e) {} }, 5000); //TODO make parameter? }; - + // Node {url, globalArg} -> Node a //load script @ url and poll until param is set, then pass it along var evalForeignScriptVal_e = function(urlArg_e) { var result = receiver_e(); urlArg_e.lift_e(function(urlArg) { runScript(urlArg.url, - function(val) { result.sendEvent(val); }, + function(val) { result.sendEvent(val); }, urlArg.globalArg); }); - + return result; }; fxExport(ws,evalForeignScriptVal_e,'evalForeignScriptVal_e'); - + var ajaxRequest = function(method,url,body,async,useFlash,callback) { var xhr; if (useFlash) { @@ -2289,18 +2289,18 @@ function flapjaxInit(options) { else if (window.ActiveXObject) { try { xhr = new ActiveXObject("Msxml2.XMLHTTP"); } catch(e) { xhr = new ActiveXObject("Microsoft.XMLHTTP"); } - + xhr.onreadystatechange = function() { if (xhr.readyState == 4) { callback(xhr); } }; }; - + xhr.open(method,url,async); - + if (method == 'POST') { xhr.setRequestHeader('Content-Type','application/x-www-form-urlencoded'); } - + xhr.send(body); return xhr; }; @@ -2413,22 +2413,22 @@ function flapjaxInit(options) { else { throw 'parseJSON: unknown object type: ' + (typeof val); } }; })(); - + var serverRequest_e = function(useFlash,requestE) { var response_e = receiver_e(); - + requestE.lift_e(function (obj) { var body = ''; var method = 'GET'; var url = obj.url; - + var reqType = obj.request ? obj.request : (obj.fields ? 'post' : 'get'); if (obj.request == 'get') { url += "?" + encodeREST(obj.fields); body = ''; method = 'GET'; } else if (obj.request == 'post') { - body = toJSONString(obj.fields); + body = toJSONString(obj.fields); method = 'POST'; } else if (obj.request == 'rawPost') { body = obj.body; @@ -2441,16 +2441,16 @@ function flapjaxInit(options) { else { raise ("Invalid request type: " + obj.request); } - + var async = obj.async; - + var xhr; - + // Branch on the response type to determine how to parse it if (obj.response == 'json') { xhr = ajaxRequest(method,url,body,async,useFlash, function(xhr) { - response_e.sendEvent(parseJSON(xhr.responseText)); + response_e.sendEvent(parseJSON(xhr.responseText)); }); } else if (obj.response == 'xml') { @@ -2469,15 +2469,15 @@ function flapjaxInit(options) { raise('Unknown response format: ' + obj.response); } }); - + return response_e; }; - + var getWebServiceObject_e = function(requestE) { return serverRequest_e(false,requestE); }; fxExport(ws,getWebServiceObject_e,'getWebServiceObject_e'); - + var getForeignWebServiceObject_e = function(requestE) { return serverRequest_e(true,requestE); }; @@ -2502,7 +2502,7 @@ fxExport(domMisc,cumulativeOffset,'cumulativeOffset'); } } } - + for (var id in exports) { if (window[id]) { if (options.redefine === false) { @@ -2517,9 +2517,9 @@ fxExport(domMisc,cumulativeOffset,'cumulativeOffset'); if (window[id] && options.redefine === false) { // Don't redefine id } - else if (options.show && options.hide && options.show[id] === true && + else if (options.show && options.hide && options.show[id] === true && options.hide[id] === true) { - throw('flapjaxInit: invalid options: ' + id + " specified as 'show' and 'hide'"); + throw('flapjaxInit: invalid options: ' + id + " specified as 'show' and 'hide'"); } else if (options.show && options.show[id]) { window[id] = exports[id]; @@ -2547,6 +2547,6 @@ fxExport(domMisc,cumulativeOffset,'cumulativeOffset'); } } } - + return exports; } |