eoc/tests/Main.hs

51 lines
1.7 KiB
Haskell

module Main where
import qualified Bril as B
import Data.Aeson (decode, toJSON, parseJSON, Result(..))
import Data.Aeson.Types (parse)
import Data.Text
import Data.Maybe
import Data.Function ((&))
import Test.HUnit
import qualified System.Exit as Exit
testTypes :: Test
testTypes = TestCase $ do
assertEqual "int type" (decode "\"int\"" :: Maybe B.Type) (Just B.Int)
assertEqual "bool type" (decode "\"bool\"" :: Maybe B.Type) (Just B.Bool)
testLiterals :: Test
testLiterals = TestCase $ do
assertEqual "true literal"
(parseLiteral B.Bool "true") (Success $ B.BoolValue True)
assertEqual "false literal"
(parseLiteral B.Bool "false") (Success $ B.BoolValue False)
assertEqual "wrong bool literal"
(parseLiteral B.Bool "xxx") (Error "invalid bool literal: xxx")
assertEqual "int literal"
(parseLiteral B.Int "1434") (Success $ B.IntValue 1434)
assertEqual "negative int literal"
(parseLiteral B.Int "-143443") (Success $ B.IntValue (- 143443))
assertEqual "wrong int literal"
(parseLiteral B.Int "123xz") (Error "invalid int literal: 123xz")
assertEqual "wrong int literal"
(parseLiteral B.Int "123.5") (Error "invalid int literal: 123.5")
assertEqual "wrong int literal"
(parseLiteral B.Int "123.5") (Error "invalid int literal: 123.5")
where
parseLiteral type_ x = (parse (B.parseValue type_) (toJSON (x::Text)))
tests :: Test
tests = TestList [
TestLabel "bril parser: type" testTypes,
TestLabel "bril parser: literal" testLiterals
]
main :: IO ()
main = do
result <- runTestTT tests
if failures result > 0 then Exit.exitFailure else Exit.exitSuccess