Newer
Older
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE LambdaCase #-}
import Control.Monad
import System.Directory
import System.FilePath
import Test.Hspec
import qualified Data.Text.Lazy as LazyText
import qualified Data.Text.Lazy.Encoding as LazyText
import Test.Hspec.Glitter
import qualified Language.C as C
import qualified Text.PrettyPrint as P
import Control.Monad.RTree (extract, iinputs, probe)
import Data.Bool
import qualified Language.C.System.GCC as C
import ReduceC
import System.Process.Typed
spec :: Spec
spec = do
specSmallCases
specLargeCases
specLargeCases :: Spec
specLargeCases = do
cases <- runIO (listDirectory "test/cases/large")
describe cfrom do
c <- runIO $ parse cfrom
let expected = "test/expected" </> dropExtensions cname
onGlitterWith (expected </> "main.c") (\fp () -> render fp c) do
it "should be valid" . foldMap $ \cf -> do
validate cf
it "should be parsed equally" . foldMap $ \cf -> do
C.parseCFilePre cf >>= \case
Left err -> fail (show err)
Right c' -> c' $> () `shouldBe` c $> ()
describe "reduction" do
it "should extract itself" do
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
IRTree.extract (defaultReduceC c) $> () `shouldBe` c $> ()
onGlitterWith
(expected </> "reduction/")
( \a () -> do
createDirectoryIfMissing True a
listDirectory a >>= mapM_ \i -> do
let idx = fromString (drop 1 (dropExtension i))
renderWithChoices
(expected </> "reduction" </> i)
(probe (defaultReduceC c) idx)
)
do
it "should validate all reductions" . mapM_ $ \a -> do
when (takeExtension a == ".c") do
validate a
specSmallCases :: Spec
specSmallCases = do
cases <- runIO (listDirectory "test/cases/small")
forM_ cases \cname -> do
let cfrom = "test/cases/small" </> cname
describe cfrom do
c <- runIO $ parse cfrom
let expected = "test/expected" </> dropExtensions cname
onGlitterWith (expected </> "main.c") (\fp () -> render fp c) do
it "should be valid" . foldMap $ \cf -> do
validate cf
it "should be parsed equally" . foldMap $ \cf -> do
C.parseCFilePre cf >>= \case
Left err -> fail (show err)
Right c' -> c' $> () `shouldBe` c $> ()
describe "reduction" do
it "should extract itself" do
extract (defaultReduceC c) $> () `shouldBe` c $> ()
onGlitterWith
(expected </> "reduction/")
( \a () -> do
_ <- tryIOError (removeDirectoryRecursive a)
createDirectoryIfMissing True a
)
do
it "should validate all reductions" . mapM_ $ \a -> do
when (takeExtension a == ".c") do
validate a
validate :: FilePath -> IO ()
validate fp = do
ExitFailure _ ->
expectationFailure $
"could not validate "
<> show fp
<> "\n"
ExitSuccess -> pure ()
render :: FilePath -> C.CTranslUnit -> IO ()
render cto c = do
createDirectoryIfMissing True (takeDirectory cto)
writeFile cto (P.render (C.pretty c) <> "\n")
renderWithChoices :: FilePath -> (C.CTranslUnit, [(Bool, (String, C.Position))]) -> IO ()
renderWithChoices file (c, a) = do
createDirectoryIfMissing True (takeDirectory file)
writeFile
file
( ( unlines
. map
( \(choice, (reason, pos)) ->
"// " <> bool "0" "1" choice <> " " <> reason <> " at " <> show pos
)
. reverse
$ a
)
<> "\n"
<> P.render (C.pretty c)
<> "\n"
)