----------------------------------------------------------------------------- -- | -- Main test module -- -- Execute 'runhaskell Tests/Tests.hs' -- from reviewboard dir -- ----------------------------------------------------------------------------- module Main where import Test.HUnit import Text.JSON import Data.Ratio import ReviewBoard.Api import ReviewBoard.Core -- | Review board test test suite -- tests = TestList [ TestLabel "Test rrFieldMap" rrFieldMapTest , TestLabel "Test jsValue" jsValueTest , TestLabel "Test jsInt" jsIntTest , TestLabel "Test jsString" jsStringTest ] -- | Main test runner -- main = runTestTT tests -- --------------------------------------------------------------------------- -- API tests -- Test rrFiledMap coverage for RRField -- TODO: do we really need a print test? rrFieldMapTest = TestCase ( do mapM (print . show) [(minBound::RRField)..(maxBound::RRField)] return () ) -- --------------------------------------------------------------------------- -- Tests JSon utils -- Helper function takes json value from result toJson :: Result (JSObject JSValue) -> JSValue toJson (Ok v) = JSObject v toJson (Error s) = error s -- Json test object testObject :: JSValue testObject = toJson $ decode "{ \"stat\" : \"fail\", \"err\" : { \"msg\" : \"test message\", \"code\" : 100 } }" statusErr :: JSValue statusErr = testObject statusOk :: JSValue statusOk = toJson $ decode "{ \"stat\" : \"ok\" }" -- Test jsValue function jsValueTest = TestCase ( do assertEqual "Empty path" (Just testObject) (jsValue [] testObject) assertEqual "One level" (Just . JSString $ toJSString "fail") (jsValue ["stat"] testObject) assertEqual "No path match" Nothing (jsValue ["no"] testObject) assertEqual "Two levels" (Just $ JSRational (100%1)) (jsValue ["err", "code"] testObject) assertEqual "One more" (Just . JSString $ toJSString "test message") (jsValue ["err", "msg"] testObject) ) -- Test jsInt function jsIntTest = TestCase ( do assertEqual "jsInt" (Just 100) (jsInt ["err", "code"] testObject) assertEqual "No path match" Nothing (jsInt ["noerr"] testObject) assertEqual "Not an int" Nothing (jsInt ["stat"] testObject) ) -- Test jsString function jsStringTest = TestCase ( do assertEqual "jsString 1" (Just "test message") (jsString ["err", "msg"] testObject) assertEqual "jsString 2" (Just "fail") (jsString ["stat"] testObject) assertEqual "jsString 2" (Just "fail") (jsString ["stat"] testObject) assertEqual "Not a string" Nothing (jsInt ["err"] testObject) )