import Test.Framework (defaultMain, testGroup, Test) import Test.Framework.Providers.HUnit import Test.HUnit hiding (Test) import Data.Char import Text.Jasmine import Language.JavaScript.Parser import Text.Jasmine.Pretty import qualified Data.ByteString.Lazy as LB import qualified Data.Text as T import qualified Data.Text.Encoding as E main :: IO () main = defaultMain [testSuite,testSuiteMin,testSuiteFiles,testSuiteFilesUnminified] testSuite :: Test testSuite = testGroup "Text.Jasmine.Parse" [ testCase "helloWorld" caseHelloWorld , testCase "helloWorld2" caseHelloWorld2 , testCase "simpleAssignment" caseSimpleAssignment , testCase "emptyFor" caseEmptyFor , testCase "fullFor" caseFullFor , testCase "forVarFull" caseForVarFull , testCase "ifelse1" caseIfElse1 , testCase "ifelse2" caseIfElse2 , testCase "0_f.js" case0_f , testCase "01_semi1.js" case01_semi1 , testCase "min_100_animals" case_min_100_animals , testCase "mergeStrings" caseMergeStrings , testCase "TrailingCommas" caseTrailingCommas , testCase "GetSet" caseGetSet , testCase "Unicode" caseUnicode , testCase "Issue3" caseIssue3 , testCase "Issue4" caseIssue4 ] testSuiteMin :: Test testSuiteMin = testGroup "Text.Jasmine.Pretty" [ testCase "helloWorld" caseMinHelloWorld , testCase "helloWorld2" caseMinHelloWorld2 , testCase "simpleAssignment" caseMinSimpleAssignment , testCase "ifelse1" caseMinIfElse1 , testCase "ifelse2" caseMinIfElse2 , testCase "0_f.js" caseMin0_f , testCase "01_semi1.js" caseMin01_semi1 , testCase "min_100_animals" caseMin_min_100_animals , testCase "minNestedSquare" caseMinNestedSquare , testCase "minMergeStrings" caseMinMergeStrings , testCase "EitherLeft" caseEitherLeft , testCase "EitherRight" caseEitherRight , testCase "TrailingCommas" caseMinTrailingCommas , testCase "GetSet" caseMinGetSet , testCase "Unicode" caseMinUnicode , testCase "MinIssue3" caseMinIssue3 , testCase "MinIssue4" caseMinIssue4 ] testSuiteFiles :: Test testSuiteFiles = testGroup "Text.Jasmine.Pretty files" [ testCase "00_f.js" (testFile "./test/pminified/00_f.js") , testCase "01_semi1.js" (testFile "./test/pminified/01_semi1.js") , testCase "02_sm.js" (testFile "./test/pminified/02_sm.js") , testCase "03_sm.js" (testFile "./test/pminified/03_sm.js") , testCase "04_if.js" (testFile "./test/pminified/04_if.js") , testCase "05_comments_simple.js" (testFile "./test/pminified/05_comments_simple.js") , testCase "05_regex.js" (testFile "./test/pminified/05_regex.js") , testCase "06_callexpr.js" (testFile "./test/pminified/06_callexpr.js") , testCase "06_newexpr.js" (testFile "./test/pminified/06_newexpr.js") , testCase "06_var.js" (testFile "./test/pminified/06_var.js") , testCase "07_expr.js" (testFile "./test/pminified/07_expr.js") , testCase "10_switch.js" (testFile "./test/pminified/10_switch.js") , testCase "14_labelled_stmts.js" (testFile "./test/pminified/14_labelled_stmts.js") , testCase "15_literals.js" (testFile "./test/pminified/15_literals.js") , testCase "16_literals.js" (testFile "./test/pminified/16_literals.js") , testCase "20_statements.js" (testFile "./test/pminified/20_statements.js") , testCase "25_trycatch.js" (testFile "./test/pminified/25_trycatch.js") , testCase "40_functions.js" (testFile "./test/pminified/40_functions.js") , testCase "67_bob.js" (testFile "./test/pminified/67_bob.js") , testCase "110_perfect.js" (testFile "./test/pminified/110_perfect.js") , testCase "120_js.js" (testFile "./test/pminified/120_js.js") , testCase "121_jsdefs.js" (testFile "./test/pminified/121_jsdefs.js") , testCase "122_jsexec.js" (testFile "./test/pminified/122_jsexec.js") , testCase "122_jsexec2.js" (testFile "./test/pminified/122_jsexec2.js") , testCase "122_jsexec3.js" (testFile "./test/pminified/122_jsexec3.js") -- , testCase "123_jsparse.js" (testFile "./test/pminified/123_jsparse.js") -- TODO: something strange here, assigning code block to variable? -- See http://msdn.microsoft.com/en-us/library/77kz8hy0.aspx, get/set keywords for object accessors --, testCase "130_htojs2.js" (testFile "./test/parsingonly/130_htojs2.js") --, testCase "" (testFile "./test/pminified/") ] testSuiteFilesUnminified :: Test testSuiteFilesUnminified = testGroup "Text.Jasmine.Pretty filesUnminified" [ testCase "00_f.js" (testFileUnminified "00_f.js") , testCase "01_semi1.js" (testFileUnminified "01_semi1.js") , testCase "02_sm.js" (testFileUnminified "02_sm.js") , testCase "03_sm.js" (testFileUnminified "03_sm.js") , testCase "04_if.js" (testFileUnminified "04_if.js") , testCase "05_comments_simple.js" (testFileUnminified "05_comments_simple.js") , testCase "05_regex.js" (testFileUnminified "05_regex.js") , testCase "06_callexpr.js" (testFileUnminified "06_callexpr.js") , testCase "06_newexpr.js" (testFileUnminified "06_newexpr.js") , testCase "06_var.js" (testFileUnminified "06_var.js") , testCase "07_expr.js" (testFileUnminified "07_expr.js") , testCase "10_switch.js" (testFileUnminified "10_switch.js") , testCase "14_labelled_stmts.js" (testFileUnminified "14_labelled_stmts.js") , testCase "15_literals.js" (testFileUnminified "15_literals.js") , testCase "16_literals.js" (testFileUnminified "16_literals.js") , testCase "20_statements.js" (testFileUnminified "20_statements.js") , testCase "25_trycatch.js" (testFileUnminified "25_trycatch.js") , testCase "40_functions.js" (testFileUnminified "40_functions.js") , testCase "67_bob.js" (testFileUnminified "67_bob.js") , testCase "110_perfect.js" (testFileUnminified "110_perfect.js") , testCase "120_js.js" (testFileUnminified "120_js.js") , testCase "121_jsdefs.js" (testFileUnminified "121_jsdefs.js") , testCase "122_jsexec.js" (testFileUnminified "122_jsexec.js") --, testCase "122_jsexec2.js" (testFileUnminified "122_jsexec2.js") ] srcHelloWorld = "function Hello(a) {}" caseHelloWorld = "Right (JSSourceElementsTop [JSFunction (JSIdentifier \"Hello\") [JSIdentifier \"a\"] (JSFunctionBody [])])" @=? (showStrippedMaybe $ parseProgram srcHelloWorld) caseMinHelloWorld = -- "function Hello(a){}" @=? (minify (U.fromString srcHelloWorld)) testMinify "function Hello(a){}" srcHelloWorld srcHelloWorld2 = "function Hello(a) {b=1}" caseHelloWorld2 = "Right (JSSourceElementsTop [JSFunction (JSIdentifier \"Hello\") [JSIdentifier \"a\"] (JSFunctionBody [JSSourceElements [JSExpression [JSIdentifier \"b\",JSOperator \"=\",JSDecimal \"1\"]]])])" @=? (showStrippedMaybe $ parseProgram srcHelloWorld2) caseMinHelloWorld2 = -- "function Hello(a){b=1}" @=? (minify (U.fromString srcHelloWorld2)) testMinify "function Hello(a){b=1}" srcHelloWorld2 srcSimpleAssignment = "a=1;" caseSimpleAssignment = "Right (JSSourceElementsTop [JSExpression [JSIdentifier \"a\",JSOperator \"=\",JSDecimal \"1\"],JSLiteral \";\"])" @=? (showStrippedMaybe $ parseProgram srcSimpleAssignment) caseMinSimpleAssignment = testMinify "a=1" srcSimpleAssignment srcEmptyFor = "for (i = 0;;){}" caseEmptyFor = "Right (JSSourceElementsTop [JSFor [JSExpression [JSIdentifier \"i\",JSOperator \"=\",JSDecimal \"0\"]] [] [] (JSStatementBlock (JSStatementList []))])" @=? (showStrippedMaybe $ parseProgram srcEmptyFor) srcFullFor = "for (i = 0;i<10;i++){}" caseFullFor = "Right (JSSourceElementsTop [JSFor [JSExpression [JSIdentifier \"i\",JSOperator \"=\",JSDecimal \"0\"]] [JSExpression [JSExpressionBinary \"<\" [JSIdentifier \"i\"] [JSDecimal \"10\"]]] [JSExpression [JSExpressionPostfix \"++\" [JSIdentifier \"i\"]]] (JSStatementBlock (JSStatementList []))])" @=? (showStrippedMaybe $ parseProgram srcFullFor) srcForVarFull = "for(var i=0,j=tokens.length;i IO () testFile filename = do x <- readFile (filename) let x' = trim x -- x' @=? (minify (U.fromString x') ) testMinify x' x' testFileUnminified :: FilePath -> IO () testFileUnminified filename = do x <- readFile ("./test/pminified/" ++ filename) y <- readFile ("./test/parsingonly/" ++ filename) let x' = trim x -- x' @=? (minify (U.fromString y)) testMinify x' y trim :: String -> String trim = f . f where f = reverse . dropWhile isSpace -- For language-javascript parseProgram src = parse src "src" -- EOF