Skip to content
Snippets Groups Projects
ReduceCSpec.hs 2.88 KiB
Newer Older
  • Learn to ignore specific revisions
  • {-# LANGUAGE BlockArguments #-}
    {-# LANGUAGE LambdaCase #-}
    
    
    module ReduceCSpec where
    
    
    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
    
    
    chrg's avatar
    chrg committed
    import Control.Monad.RTree (extract, iinputs, probe)
    import Data.Bool
    
    import Data.Functor
    import Data.RPath
    import qualified Language.C.System.GCC as C
    import ReduceC
    
    chrg's avatar
    chrg committed
    import System.Directory.Internal.Prelude (tryIOError)
    
    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
    
    
    chrg's avatar
    chrg committed
        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
              fmap ($> ()) (extract $ defaultReduceC c) `shouldBe` Just (c $> ())
    
          onGlitterWith
            (expected </> "reduction/")
            ( \a () -> do
                _ <- tryIOError (removeDirectoryRecursive a)
                createDirectoryIfMissing True a
                forM_ (iinputs (defaultReduceC c)) \(i, c') -> do
                  let rfile = expected </> "reduction" </> "r" <> debugShow i <.> "c"
                  maybe (writeFile rfile "") (render rfile) c'
                  let cofile = expected </> "reduction" </> "r" <> debugShow i <.> "choices"
                  writeFile
                    cofile
                    ( unlines
                        . map (\(choice, (reason, pos)) -> bool "0" "1" choice <> " " <> reason <> " at " <> show pos)
                        . snd
                        $ probe (defaultReduceC c) i
                    )
            )
            do
              it "should validate all reductions" . mapM_ $ \a -> do
                when (takeExtension a == ".c") do
                  validate a
    
    
    validate :: FilePath -> IO ()
    validate fp = do
    
    chrg's avatar
    chrg committed
      (ec, _, stderr) <- readProcess (proc "clang" ["-o", "/dev/null", fp])
    
      case ec of
    
        ExitFailure _ ->
          expectationFailure $
            "could not validate "
              <> show fp
              <> "\n"
    
    chrg's avatar
    chrg committed
              <> LazyText.unpack (LazyText.decodeUtf8 stderr)
    
        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'