module Golden where import Control.Monad (Monad(..)) import Data.Function (($), (.)) import Data.Functor ((<$>)) import Data.Semigroup (Semigroup(..)) import Data.String (String) -- import System.FilePath (FilePath) import System.IO (IO) import qualified Data.ByteString.Lazy as BSL import qualified Data.List as List import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Encoding as TL import Test.Tasty import Test.Tasty.Golden import Language.Symantic.Grammar import Language.Symantic import Language.Symantic.Lib () -- * Golden testing utilities testGolden :: TestName -> TestName -> IO BSL.ByteString -> TestTree testGolden inputFile expectedExt = goldenVsStringDiff inputFile diffGolden (inputFile <> expectedExt) diffGolden :: FilePath -> FilePath -> [String] diffGolden ref new = ["diff", "-u", ref, new] -- * All golden tests goldensIO :: IO TestTree goldensIO = do -- inputFiles <- List.sort <$> findByExtension [".sym"] "test/Golden" return $ testGroup "Golden" [ testGolden "grammar.ebnf" "" $ do return $ TL.encodeUtf8 $ TL.unlines $ List.concat [ render <$> gram_comment , render <$> gram_type , render <$> gram_term ] ] where render = TL.fromStrict . renderEBNF . unCF