rubyhs/test/Main.hs

36 lines
1.1 KiB
Haskell
Raw Permalink Normal View History

2019-10-18 20:20:26 +00:00
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -Wall #-}
2019-10-18 20:20:26 +00:00
module Main (main) where
import Frelude
import Test.Tasty
import Test.Tasty.HUnit
import qualified Data.Language.Ruby as Ruby
import qualified Rubyhs.References as Ruby
import qualified Data.Aeson as Aeson
import System.FilePath
import Data.HashMap.Strict (HashMap)
import Data.Set (Set)
import System.Directory (withCurrentDirectory)
main :: IO ()
main = withCurrentDirectory "test" $ defaultMain $ testGroup "Unit tests" tests
tests :: [TestTree]
tests = go <$> ["mod", "simple", "nested", "closest", "assignment"]
2019-10-18 20:20:26 +00:00
where
go :: String -> TestTree
go s = testCase s $ do
let basename = "tests" </> s
begin <- Ruby.parseFile @Ruby.Begin $ basename <.> "rb"
json <- decodeFile @(HashMap Ruby.Node (Set Ruby.Node)) $ basename <.> "json"
let (Ruby.Result refs) = Ruby.references begin
when (refs /= json)
$ assertFailure
2019-10-20 20:14:50 +00:00
$ "Expected " <> convertString (Aeson.encode json) <> " but got " <> convertString (Aeson.encode refs)
2019-10-18 20:20:26 +00:00
decodeFile :: FromJSON a => FilePath -> IO a
decodeFile p = Aeson.eitherDecodeFileStrict' p >>= \case
Left err -> error err
Right a -> pure a