Skip to content
Snippets Groups Projects
ReduceCSpec.hs 2.26 KiB
Newer Older
  • Learn to ignore specific revisions
  • chrg's avatar
    chrg committed
    {-# LANGUAGE BlockArguments #-}
    {-# LANGUAGE LambdaCase #-}
    
    
    chrg's avatar
    chrg committed
    module ReduceCSpec where
    
    
    chrg's avatar
    chrg committed
    import Control.Monad
    
    import System.Directory
    import System.FilePath
    import Test.Hspec
    
    
    chrg's avatar
    chrg committed
    import qualified Data.Text.Lazy as LazyText
    import qualified Data.Text.Lazy.Encoding as LazyText
    
    
    chrg's avatar
    chrg committed
    import Test.Hspec.Glitter
    
    import qualified Language.C as C
    import qualified Text.PrettyPrint as P
    
    import Control.Monad.RTree (extract, iinputs)
    import Data.Functor
    import Data.RPath
    import qualified Language.C.System.GCC as C
    import ReduceC
    import System.Process.Typed
    
    spec :: Spec
    spec = do
      cases <- runIO (listDirectory "test/cases")
    
      forM_ cases \cname -> do
    
    chrg's avatar
    chrg committed
        let cfrom = "test/cases" </> cname
    
        c <- runIO $ parse cfrom
    
    chrg's avatar
    chrg committed
        let expected = "test/expected" </> dropExtensions cname
        onGlitterWith (expected </> "main.c") (\fp () -> render fp c) do
          it "should be valid" . foldMap $ \cf -> do
            validate cf
    
    chrg's avatar
    chrg committed
          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
    
    chrg's avatar
    chrg committed
            extract (defaultReduceC c) `shouldBe` c
    
    chrg's avatar
    chrg committed
    
        onGlitterWith
    
    chrg's avatar
    chrg committed
          (expected </> "reduction/")
    
    chrg's avatar
    chrg committed
          ( \a () -> do
    
    chrg's avatar
    chrg committed
              removeDirectoryRecursive a
    
    chrg's avatar
    chrg committed
              createDirectoryIfMissing True a
    
    chrg's avatar
    chrg committed
              forM_ (take 20 $ iinputs (defaultReduceC c)) \(i, c') -> do
    
    chrg's avatar
    chrg committed
                let rfile = expected </> "reduction" </> "r" <> debugShow i <.> "c"
                render rfile c'
          )
          do
    
    chrg's avatar
    chrg committed
            it "should validate all reductions" . mapM_ $ \a -> do
              validate a
    
    chrg's avatar
    chrg committed
    
    validate :: FilePath -> IO ()
    validate fp = do
    
    chrg's avatar
    chrg committed
      (ec, res) <- readProcessStderr (proc "clang" ["-o", "/dev/null", fp])
    
    chrg's avatar
    chrg committed
      case ec of
    
    chrg's avatar
    chrg committed
        ExitFailure _ ->
          expectationFailure $
            "could not validate "
              <> show fp
              <> "\n"
              <> LazyText.unpack (LazyText.decodeUtf8 res)
    
    chrg's avatar
    chrg committed
        ExitSuccess -> pure ()
    
    render :: FilePath -> C.CTranslUnit -> IO ()
    render cto c = do
      createDirectoryIfMissing True (takeDirectory cto)
      writeFile cto (P.render (C.pretty c) <> "\n")
    
    parse :: FilePath -> IO C.CTranslUnit
    parse cfrom = do
      cf <- C.parseCFile (C.newGCC "clang") Nothing [] cfrom
      case cf of
        Left err -> fail (show err)
        Right cf' -> pure cf'