Skip to content
Snippets Groups Projects
ReduceCSpec.hs 6.65 KiB
Newer Older
  • Learn to ignore specific revisions
  • {-# LANGUAGE BlockArguments #-}
    {-# LANGUAGE LambdaCase #-}
    
    chrg's avatar
    chrg committed
    {-# LANGUAGE OverloadedStrings #-}
    
    module ReduceCSpec where
    
    
    import Control.Monad
    
    chrg's avatar
    chrg committed
    import qualified Control.Monad.IRTree as IRTree
    
    chrg's avatar
    chrg committed
    import qualified Control.Monad.RTree as RTree
    
    import Data.Bits
    
    chrg's avatar
    chrg committed
    import Data.Function
    
    import Data.Functor
    import Data.RPath
    
    chrg's avatar
    chrg committed
    import Data.String
    
    chrg's avatar
    chrg committed
    import qualified Data.Text.Lazy as LazyText
    import qualified Data.Text.Lazy.Encoding as LazyText
    import qualified Language.C as C
    
    import qualified Language.C.System.GCC as C
    import ReduceC
    
    chrg's avatar
    chrg committed
    import System.Directory
    
    chrg's avatar
    chrg committed
    import System.Directory.Internal.Prelude (tryIOError)
    
    chrg's avatar
    chrg committed
    import System.FilePath
    
    import System.Process.Typed
    
    chrg's avatar
    chrg committed
    import Test.Hspec
    import qualified Test.Hspec.Expectations.Pretty as EP
    import Test.Hspec.Glitter
    import qualified Text.PrettyPrint as P
    
    
    spec :: Spec
    spec = do
    
    chrg's avatar
    chrg committed
      specSmallCases
    
    chrg's avatar
    chrg committed
      specLargeCases
    
    
    chrg's avatar
    chrg committed
    specSmallCases :: Spec
    specSmallCases = do
      let testcases = "test" </> "cases" </> "small"
      cases <- runIO (listDirectory testcases)
    
    
      forM_ cases \cname -> do
    
    chrg's avatar
    chrg committed
        let cfrom = testcases </> cname
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
        describe cfrom do
          c <- runIO $ parse cfrom
    
    
    chrg's avatar
    chrg committed
          let expected = "test" </> "expected" </> dropExtensions cname
    
    
          -- onGlitter (expected </> "main.hs") (\f -> LazyText.writeFile f (PS.pShowNoColor (void c))) do
          --   pure ()
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
          onGlitter (expected </> "main.c") (`render` c) do
    
    chrg's avatar
    chrg committed
            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)
    
    chrg's avatar
    chrg committed
                Right c' -> void c' `EP.shouldBe` void c
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
          describe "reduction" do
            it "should extract itself" do
              IRTree.extract (defaultReduceC c) $> () `EP.shouldBe` c $> ()
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
          onGlitterEach
            (expected </> "reduction")
    
    chrg's avatar
    chrg committed
            ( \a -> do
                _ <- tryIOError (removeDirectoryRecursive a)
                createDirectoryIfMissing True a
    
                let examples = RTree.iinputs (defaultReduceC c)
                forM_ examples \(i, _) -> do
    
    chrg's avatar
    chrg committed
                  let rfile = expected </> "reduction" </> "r" <> debugShow i <.> "c"
                  renderWithChoices rfile (IRTree.probe (defaultReduceC c) i)
    
                when (length examples > 50) $ fail "too many examples - simplify test case"
    
    chrg's avatar
    chrg committed
            )
            do
    
    chrg's avatar
    chrg committed
              it "should validate all reductions" $ \a -> do
    
    chrg's avatar
    chrg committed
                when (takeExtension a == ".c") do
                  validate a
    
    
    chrg's avatar
    chrg committed
    specLargeCases :: Spec
    
    specLargeCases = focus do
    
    chrg's avatar
    chrg committed
      cases <- runIO (listDirectory "test/cases/large")
    
    chrg's avatar
    chrg committed
    
    
      let cases' = filter (\c -> c == "gcc-71626.c") cases
    
      forM_ cases' \cname -> do
    
    chrg's avatar
    chrg committed
        let cfrom = "test" </> "cases" </> "large" </> cname
        let expected = "test" </> "expected" </> dropExtensions cname
    
    chrg's avatar
    chrg committed
    
        describe cfrom do
          c <- runIO $ parse cfrom
    
    
    chrg's avatar
    chrg committed
          onGlitter (expected </> "main.c") (`render` c) do
    
    chrg's avatar
    chrg committed
            it "should be valid" . foldMap $ \cf -> do
    
    chrg's avatar
    chrg committed
              simplevalidate cf
    
    chrg's avatar
    chrg committed
    
            it "should be parsed equally" . foldMap $ \cf -> do
              C.parseCFilePre cf >>= \case
                Left err -> fail (show err)
    
    chrg's avatar
    chrg committed
                Right c' -> c' $> () `shouldBe` c $> ()
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
          onGlitterEach (expected </> "extract.c") (\fp -> render fp (IRTree.extract (defaultReduceC c))) do
            it "should be parsed equally" $ \cf -> do
              C.parseCFilePre cf >>= \case
                Left err -> fail (show err)
                Right c' -> when (void c' /= void c) do
                  expectationFailure "did not parse as we extracted"
    
    chrg's avatar
    chrg committed
    
    
    chrg's avatar
    chrg committed
          onGlitterEach
            (expected </> "reduction")
    
    chrg's avatar
    chrg committed
            ( \fp -> do
                _ <- tryIOError (removeDirectoryRecursive fp)
                createDirectoryIfMissing True fp
                0 & fix \rec n -> do
                  let idx = fromString (replicate (1 `shiftL` n) '1')
                  let (c', t, _) = IRTree.probe (defaultReduceC c) idx
                  render (fp </> "x" <> show n <.> "c") c'
                  renderChoices (fp </> "p" <> show n <.> "path") t
                  unless (all ((/= Undecided) . choice) t) do
                    rec (n + 1)
    
    chrg's avatar
    chrg committed
            )
    
    chrg's avatar
    chrg committed
            do
              it "should validate all reductions" $ \a -> do
                when (takeExtension a == ".c") do
    
    chrg's avatar
    chrg committed
                  simplevalidate a
    
    
    validate :: FilePath -> IO ()
    validate fp = do
    
    chrg's avatar
    chrg committed
      (ec, _, stderr_) <-
        readProcess
          ( proc
              "clang"
              [ "-Werror"
    
              , "-Wno-error=int-conversion"
    
    chrg's avatar
    chrg committed
              , "-Wno-error=unused-value"
              , "-Wno-error=return-type"
              , "-Wno-error=incompatible-library-redeclaration"
    
              , "-std=gnu89"
    
    chrg's avatar
    chrg committed
              , "-o"
              , "/dev/null"
              , fp
              ]
          )
      case ec of
        ExitFailure _ ->
          expectationFailure $
            "could not validate "
              <> show fp
              <> "\n"
              <> ( LazyText.unpack
                    . LazyText.unlines
                    . filter (LazyText.isInfixOf "error")
                    . LazyText.lines
                    $ LazyText.decodeUtf8 stderr_
                 )
        ExitSuccess -> pure ()
    
    simplevalidate :: FilePath -> IO ()
    simplevalidate fp = do
      (ec, _, stderr_) <-
    
        readProcess
          ( proc
              "clang"
              [ -- "-Wno-error=int-conversion"
                "-std=gnu89"
              , "-o"
              , "/dev/null"
              , fp
              ]
          )
    
      case ec of
    
        ExitFailure _ ->
          expectationFailure $
    
            "could not simple validate "
    
              <> show fp
              <> "\n"
    
              <> ( LazyText.unpack
                    . LazyText.unlines
                    . filter (LazyText.isInfixOf "error")
                    . LazyText.lines
    
    chrg's avatar
    chrg committed
                    $ 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")
    
    
    chrg's avatar
    chrg committed
    renderChoices :: FilePath -> [AnnotatedChoice (String, C.Position)] -> IO ()
    renderChoices file as =
      writeFile
        file
        ( ( unlines
              . map
                ( \(AnnotatedChoice cs (reason, pos)) ->
                    [debugShowChoice cs] <> " " <> reason <> " at " <> show pos
                )
              $ as
          )
            <> "\n"
        )
    
    
    chrg's avatar
    chrg committed
    renderWithChoices :: FilePath -> (C.CTranslUnit, [AnnotatedChoice (String, C.Position)], Int) -> IO ()
    renderWithChoices file (c, a, _) = do
    
    chrg's avatar
    chrg committed
      createDirectoryIfMissing True (takeDirectory file)
      writeFile
        file
        ( ( unlines
              . map
    
    chrg's avatar
    chrg committed
                ( \(AnnotatedChoice cs (reason, pos)) ->
                    "// " <> [debugShowChoice cs] <> " " <> reason <> " at " <> show pos
    
    chrg's avatar
    chrg committed
      appendFile
        file
        (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'