From 9a263465c7c64b414e79e075d3b7ef09898d2b8d Mon Sep 17 00:00:00 2001 From: Christian Gram Kalhauge <chrg@dtu.dk> Date: Mon, 26 Feb 2024 14:47:21 +0100 Subject: [PATCH] Semi-working version --- rtree-c/.hspec | 1 + rtree-c/develop.sh | 2 +- rtree-c/src/ReduceC.hs | 562 ++++++++++++------ rtree-c/test/cases/large/llvm-26760.c | 28 + rtree-c/test/cases/{ => small}/constant.c | 0 rtree-c/test/cases/{ => small}/main.c | 0 rtree-c/test/cases/{ => small}/typedef.c | 0 rtree-c/test/cases/{ => small}/while-loops.c | 0 .../test/expected/constant/reduction/r000.c | 6 - .../expected/constant/reduction/r000.choices | 3 - .../expected/constant/reduction/r000000.c | 13 + .../expected/constant/reduction/r000001.c | 13 + .../test/expected/constant/reduction/r00001.c | 12 + .../test/expected/constant/reduction/r0001.c | 11 + .../test/expected/constant/reduction/r001.c | 4 + .../expected/constant/reduction/r001.choices | 3 - .../test/expected/constant/reduction/r010.c | 5 - .../expected/constant/reduction/r010.choices | 3 - .../expected/constant/reduction/r010000.c | 12 + .../expected/constant/reduction/r010001.c | 12 + .../test/expected/constant/reduction/r01001.c | 11 + .../test/expected/constant/reduction/r0101.c | 10 + .../test/expected/constant/reduction/r011.c | 4 + .../expected/constant/reduction/r011.choices | 3 - .../test/expected/constant/reduction/r100.c | 5 - .../expected/constant/reduction/r100.choices | 3 - .../expected/constant/reduction/r100000.c | 12 + .../expected/constant/reduction/r100001.c | 12 + .../test/expected/constant/reduction/r10001.c | 11 + .../test/expected/constant/reduction/r1001.c | 10 + .../test/expected/constant/reduction/r101.c | 4 + .../expected/constant/reduction/r101.choices | 3 - .../test/expected/constant/reduction/r110.c | 4 - .../expected/constant/reduction/r110.choices | 3 - .../expected/constant/reduction/r110000.c | 11 + .../expected/constant/reduction/r110001.c | 11 + .../test/expected/constant/reduction/r11001.c | 10 + .../test/expected/constant/reduction/r1101.c | 9 + .../test/expected/constant/reduction/r111.c | 4 + .../expected/constant/reduction/r111.choices | 3 - rtree-c/test/expected/llvm-26760/main.c | 34 ++ .../test/expected/llvm-26760/reduction/r1.c | 71 +++ .../test/expected/llvm-26760/reduction/r11.c | 70 +++ .../test/expected/llvm-26760/reduction/r111.c | 69 +++ .../expected/llvm-26760/reduction/r1111.c | 68 +++ .../expected/llvm-26760/reduction/r11111.c | 67 +++ .../expected/llvm-26760/reduction/r111110.c | 67 +++ .../expected/llvm-26760/reduction/r1111101.c | 60 ++ .../expected/llvm-26760/reduction/r11111011.c | 57 ++ .../llvm-26760/reduction/r111110111.c | 44 ++ .../llvm-26760/reduction/r1111101111.c | 36 ++ rtree-c/test/expected/main/reduction/r.c | 1 + .../test/expected/main/reduction/r.choices | 0 .../test/expected/typedef/reduction/r0000.c | 9 - .../expected/typedef/reduction/r0000.choices | 4 - .../test/expected/typedef/reduction/r00000.c | 15 + .../test/expected/typedef/reduction/r00001.c | 15 + .../test/expected/typedef/reduction/r0001.c | 5 + .../expected/typedef/reduction/r0001.choices | 4 - .../test/expected/typedef/reduction/r0010.c | 8 - .../expected/typedef/reduction/r0010.choices | 4 - .../test/expected/typedef/reduction/r00100.c | 14 + .../test/expected/typedef/reduction/r00101.c | 14 + .../test/expected/typedef/reduction/r0011.c | 5 + .../expected/typedef/reduction/r0011.choices | 4 - .../test/expected/typedef/reduction/r0100.c | 6 - .../expected/typedef/reduction/r0100.choices | 4 - .../test/expected/typedef/reduction/r01000.c | 12 + .../test/expected/typedef/reduction/r01001.c | 12 + .../test/expected/typedef/reduction/r0101.c | 5 + .../expected/typedef/reduction/r0101.choices | 4 - .../test/expected/typedef/reduction/r0110.c | 5 - .../expected/typedef/reduction/r0110.choices | 4 - .../test/expected/typedef/reduction/r01100.c | 11 + .../test/expected/typedef/reduction/r01101.c | 11 + .../test/expected/typedef/reduction/r0111.c | 5 + .../expected/typedef/reduction/r0111.choices | 4 - .../test/expected/typedef/reduction/r1000.c | 8 - .../expected/typedef/reduction/r1000.choices | 4 - .../test/expected/typedef/reduction/r10000.c | 14 + .../test/expected/typedef/reduction/r10001.c | 14 + .../test/expected/typedef/reduction/r1001.c | 5 + .../expected/typedef/reduction/r1001.choices | 4 - .../test/expected/typedef/reduction/r1010.c | 7 - .../expected/typedef/reduction/r1010.choices | 4 - .../test/expected/typedef/reduction/r10100.c | 13 + .../test/expected/typedef/reduction/r10101.c | 13 + .../test/expected/typedef/reduction/r1011.c | 5 + .../expected/typedef/reduction/r1011.choices | 4 - .../test/expected/typedef/reduction/r1100.c | 5 - .../expected/typedef/reduction/r1100.choices | 4 - .../test/expected/typedef/reduction/r11000.c | 11 + .../test/expected/typedef/reduction/r11001.c | 11 + .../test/expected/typedef/reduction/r1101.c | 5 + .../expected/typedef/reduction/r1101.choices | 4 - .../test/expected/typedef/reduction/r1110.c | 4 - .../expected/typedef/reduction/r1110.choices | 4 - .../test/expected/typedef/reduction/r11100.c | 10 + .../test/expected/typedef/reduction/r11101.c | 10 + .../test/expected/typedef/reduction/r1111.c | 5 + .../expected/typedef/reduction/r1111.choices | 4 - .../expected/while-loops/reduction/r000.c | 8 - .../while-loops/reduction/r000.choices | 3 - .../expected/while-loops/reduction/r0000000.c | 16 + .../expected/while-loops/reduction/r0000001.c | 16 + .../expected/while-loops/reduction/r000001.c | 14 + .../expected/while-loops/reduction/r0000100.c | 16 + .../expected/while-loops/reduction/r0000101.c | 16 + .../expected/while-loops/reduction/r000011.c | 14 + .../expected/while-loops/reduction/r000100.c | 15 + .../expected/while-loops/reduction/r000101.c | 15 + .../expected/while-loops/reduction/r00011.c | 13 + .../expected/while-loops/reduction/r001.c | 7 - .../while-loops/reduction/r001.choices | 3 - .../expected/while-loops/reduction/r00100.c | 14 + .../expected/while-loops/reduction/r00101.c | 14 + .../expected/while-loops/reduction/r0011.c | 12 + .../test/expected/while-loops/reduction/r01.c | 3 + .../while-loops/reduction/r01.choices | 2 - .../expected/while-loops/reduction/r100.c | 7 - .../while-loops/reduction/r100.choices | 3 - .../expected/while-loops/reduction/r10000.c | 12 + .../expected/while-loops/reduction/r10001.c | 12 + .../expected/while-loops/reduction/r1001.c | 11 + .../expected/while-loops/reduction/r101.c | 6 +- .../while-loops/reduction/r101.choices | 3 - .../test/expected/while-loops/reduction/r11.c | 3 + .../while-loops/reduction/r11.choices | 2 - rtree-c/test/src/ReduceCSpec.hs | 82 ++- 129 files changed, 1773 insertions(+), 402 deletions(-) create mode 100644 rtree-c/test/cases/large/llvm-26760.c rename rtree-c/test/cases/{ => small}/constant.c (100%) rename rtree-c/test/cases/{ => small}/main.c (100%) rename rtree-c/test/cases/{ => small}/typedef.c (100%) rename rtree-c/test/cases/{ => small}/while-loops.c (100%) delete mode 100644 rtree-c/test/expected/constant/reduction/r000.c delete mode 100644 rtree-c/test/expected/constant/reduction/r000.choices create mode 100644 rtree-c/test/expected/constant/reduction/r000000.c create mode 100644 rtree-c/test/expected/constant/reduction/r000001.c create mode 100644 rtree-c/test/expected/constant/reduction/r00001.c create mode 100644 rtree-c/test/expected/constant/reduction/r0001.c delete mode 100644 rtree-c/test/expected/constant/reduction/r001.choices delete mode 100644 rtree-c/test/expected/constant/reduction/r010.c delete mode 100644 rtree-c/test/expected/constant/reduction/r010.choices create mode 100644 rtree-c/test/expected/constant/reduction/r010000.c create mode 100644 rtree-c/test/expected/constant/reduction/r010001.c create mode 100644 rtree-c/test/expected/constant/reduction/r01001.c create mode 100644 rtree-c/test/expected/constant/reduction/r0101.c delete mode 100644 rtree-c/test/expected/constant/reduction/r011.choices delete mode 100644 rtree-c/test/expected/constant/reduction/r100.c delete mode 100644 rtree-c/test/expected/constant/reduction/r100.choices create mode 100644 rtree-c/test/expected/constant/reduction/r100000.c create mode 100644 rtree-c/test/expected/constant/reduction/r100001.c create mode 100644 rtree-c/test/expected/constant/reduction/r10001.c create mode 100644 rtree-c/test/expected/constant/reduction/r1001.c delete mode 100644 rtree-c/test/expected/constant/reduction/r101.choices delete mode 100644 rtree-c/test/expected/constant/reduction/r110.c delete mode 100644 rtree-c/test/expected/constant/reduction/r110.choices create mode 100644 rtree-c/test/expected/constant/reduction/r110000.c create mode 100644 rtree-c/test/expected/constant/reduction/r110001.c create mode 100644 rtree-c/test/expected/constant/reduction/r11001.c create mode 100644 rtree-c/test/expected/constant/reduction/r1101.c delete mode 100644 rtree-c/test/expected/constant/reduction/r111.choices create mode 100644 rtree-c/test/expected/llvm-26760/main.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r1.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r11.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r111.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r1111.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r11111.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r111110.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r1111101.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r11111011.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r111110111.c create mode 100644 rtree-c/test/expected/llvm-26760/reduction/r1111101111.c delete mode 100644 rtree-c/test/expected/main/reduction/r.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r0000.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0000.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r00000.c create mode 100644 rtree-c/test/expected/typedef/reduction/r00001.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0001.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r0010.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0010.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r00100.c create mode 100644 rtree-c/test/expected/typedef/reduction/r00101.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0011.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r0100.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0100.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r01000.c create mode 100644 rtree-c/test/expected/typedef/reduction/r01001.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0101.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r0110.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0110.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r01100.c create mode 100644 rtree-c/test/expected/typedef/reduction/r01101.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r0111.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r1000.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1000.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r10000.c create mode 100644 rtree-c/test/expected/typedef/reduction/r10001.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1001.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r1010.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1010.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r10100.c create mode 100644 rtree-c/test/expected/typedef/reduction/r10101.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1011.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r1100.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1100.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r11000.c create mode 100644 rtree-c/test/expected/typedef/reduction/r11001.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1101.choices delete mode 100644 rtree-c/test/expected/typedef/reduction/r1110.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1110.choices create mode 100644 rtree-c/test/expected/typedef/reduction/r11100.c create mode 100644 rtree-c/test/expected/typedef/reduction/r11101.c delete mode 100644 rtree-c/test/expected/typedef/reduction/r1111.choices delete mode 100644 rtree-c/test/expected/while-loops/reduction/r000.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r000.choices create mode 100644 rtree-c/test/expected/while-loops/reduction/r0000000.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r0000001.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r000001.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r0000100.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r0000101.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r000011.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r000100.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r000101.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r00011.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r001.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r001.choices create mode 100644 rtree-c/test/expected/while-loops/reduction/r00100.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r00101.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r0011.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r01.choices delete mode 100644 rtree-c/test/expected/while-loops/reduction/r100.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r100.choices create mode 100644 rtree-c/test/expected/while-loops/reduction/r10000.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r10001.c create mode 100644 rtree-c/test/expected/while-loops/reduction/r1001.c delete mode 100644 rtree-c/test/expected/while-loops/reduction/r101.choices delete mode 100644 rtree-c/test/expected/while-loops/reduction/r11.choices diff --git a/rtree-c/.hspec b/rtree-c/.hspec index 6e9b625..c72f5b3 100644 --- a/rtree-c/.hspec +++ b/rtree-c/.hspec @@ -1,2 +1,3 @@ --failure-report .hspec-failures +--fail-fast --rerun-all-on-success diff --git a/rtree-c/develop.sh b/rtree-c/develop.sh index a661dcf..d8dbb7d 100755 --- a/rtree-c/develop.sh +++ b/rtree-c/develop.sh @@ -1 +1 @@ -ghcid --command='cabal repl rtree-c-test' -r --reload=test/cases +ghcid --command='cabal repl rtree-c-test' -r --reload=test/cases diff --git a/rtree-c/src/ReduceC.hs b/rtree-c/src/ReduceC.hs index b6c5c38..a537682 100644 --- a/rtree-c/src/ReduceC.hs +++ b/rtree-c/src/ReduceC.hs @@ -11,15 +11,25 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE NoMonomorphismRestriction #-} -module ReduceC where +module ReduceC ( + defaultReduceC, + reduceCTranslUnit, + + -- * Context + Context (..), + defaultContext, + + -- * Helpers + prettyIdent, +) where -import Control.Monad.Reader import Control.Monad.Reduce -import Control.Monad.Trans.Maybe (MaybeT (runMaybeT)) import Data.Data import Data.Foldable +import Data.Function import Data.Functor import qualified Data.Map.Strict as Map +import Data.Maybe import qualified Data.Set as Set import Data.Vector.Internal.Check (HasCallStack) import qualified Language.C as C @@ -36,12 +46,13 @@ data Keyword | DoNoops | NoSemantics | AllowEmptyDeclarations + | DisallowVariableInlining deriving (Show, Read, Enum, Eq, Ord) -type CM m = (MonadReduce (String, C.Position) m, MonadReader Context m, MonadFail m) +type Lab = (String, C.Position) -defaultReduceC :: (CReducible a, MonadReduce (String, C.Position) m) => a -> m (Maybe a) -defaultReduceC a = runMaybeT (runReaderT (reduceC a) defaultContext) +defaultReduceC :: (MonadReduce (String, C.Position) m) => C.CTranslUnit -> m C.CTranslUnit +defaultReduceC a = reduceCTranslUnit a defaultContext addTypeDefs :: [C.Ident] -> [C.CDeclarationSpecifier C.NodeInfo] -> Context -> Context addTypeDefs ids cs Context{..} = @@ -58,6 +69,20 @@ addInlineExpr i e Context{..} = , .. } +addKeyword :: Keyword -> Context -> Context +addKeyword k Context{..} = + Context + { keywords = Set.insert k keywords + , .. + } + +-- deleteKeyword :: Keyword -> Context -> Context +-- deleteKeyword k Context{..} = +-- Context +-- { keywords = Set.delete k keywords +-- , .. +-- } + defaultContext :: Context defaultContext = Context @@ -66,127 +91,241 @@ defaultContext = , inlineExprs = Map.empty } -keyword :: (MonadReader Context m) => Keyword -> m Bool -keyword s = asks (Set.member s . keywords) - -class CReducible a where - reduceC :: (CM m) => a -> m a - -instance CReducible C.CTranslUnit where - reduceC (C.CTranslUnit es ni) = do - es' <- foldr reduceCExternalDeclaration (pure []) es - pure $ C.CTranslUnit es' ni - where - reduceCExternalDeclaration r cont = do - shouldKeepMain <- keyword KeepMain - case r of - C.CFDefExt fun - | shouldKeepMain && maybe False (("main" ==) . C.identToString) (functionName fun) -> do - r' <- C.CFDefExt <$> reduceC fun - (r' :) <$> cont - | otherwise -> - split ("remove function " <> maybe "" C.identToString (functionName fun), C.posOf r) cont do - r' <- C.CFDefExt <$> reduceC fun - (r' :) <$> cont - C.CDeclExt result -> - case result of - -- A typedef - C.CDecl (C.CStorageSpec (C.CTypedef n) : rst) decl _ -> do - let [ids] = identifiers decl - split - ("inline typedef " <> C.identToString ids, C.posOf r) - (local (addTypeDefs [ids] rst) cont) - ((r :) <$> local (addTypeDefs [ids] [C.CTypeSpec (C.CTypeDef ids n)]) cont) - -- A const - C.CDecl rec decl ni' -> do - (decl', cont') <- foldr reduceCDeclarationItem (pure ([], cont)) decl - allow <- keyword AllowEmptyDeclarations - case decl' of - [] - | allow -> - split ("remove empty declaration", C.posOf r) cont' do - (C.CDeclExt (C.CDecl rec decl' ni') :) <$> cont' - | otherwise -> cont' - _ow -> (C.CDeclExt (C.CDecl rec decl' ni') :) <$> cont' - a -> don'tHandle a - _r -> don'tHandle r +isIn :: Keyword -> Context -> Bool +isIn k = Set.member k . keywords + +prettyIdent :: C.Identifier C.NodeInfo -> [Char] +prettyIdent (C.Ident s _ a) = s ++ " at " ++ show (C.posOfNode a) + +reduceCTranslUnit + :: (MonadReduce Lab m) + => C.CTranslationUnit C.NodeInfo + -> Context + -> m (C.CTranslationUnit C.NodeInfo) +reduceCTranslUnit (C.CTranslUnit es ni) ctx = do + es' <- foldr reduceCExternalDeclaration (\_ -> pure []) es ctx + pure $ C.CTranslUnit es' ni + +reduceCExternalDeclaration + :: (MonadReduce Lab m) + => C.CExternalDeclaration C.NodeInfo + -> (Context -> m [C.CExternalDeclaration C.NodeInfo]) + -> Context + -> m [C.CExternalDeclaration C.NodeInfo] +reduceCExternalDeclaration r cont ctx = do + case inlineTypeDefs r ctx of + C.CFDefExt fun + | KeepMain `isIn` ctx && maybe False (("main" ==) . C.identToString) (functionName fun) -> do + r' <- C.CFDefExt <$> reduceCFunDef fun ctx + (r' :) <$> cont ctx + | otherwise -> + split ("remove function " <> maybe "" C.identToString (functionName fun), C.posOf r) (cont ctx) do + r' <- C.CFDefExt <$> reduceCFunDef fun ctx + (r' :) <$> cont ctx + C.CDeclExt result -> + case result of + -- A typedef + C.CDecl (C.CStorageSpec (C.CTypedef n) : rst) decl _ -> do + let [ids] = identifiers decl + split + ("inline typedef " <> C.identToString ids, C.posOf r) + (cont (addTypeDefs [ids] rst ctx)) + ((r :) <$> cont (addTypeDefs [ids] [C.CTypeSpec (C.CTypeDef ids n)] ctx)) + -- A const + C.CDecl rec decl ni' -> do + (decl', ctx') <- foldr reduceCDeclarationItem (pure ([], ctx)) decl + case decl' of + [] + | AllowEmptyDeclarations `isIn` ctx' -> + split ("remove empty declaration", C.posOf r) (cont ctx') do + (C.CDeclExt (C.CDecl rec decl' ni') :) <$> cont ctx' + | otherwise -> cont ctx' + _ow -> (C.CDeclExt (C.CDecl rec decl' ni') :) <$> cont ctx' + a -> don'tHandle a + _r -> don'tHandle r + +reduceCFunDef + :: (MonadReduce Lab m) + => C.CFunctionDef C.NodeInfo + -> Context + -> m (C.CFunctionDef C.NodeInfo) +reduceCFunDef (C.CFunDef spc dec cdecls smt ni) ctx = do + smt' <- reduceCStatementOrEmptyBlock smt ctx + pure $ C.CFunDef spc dec cdecls smt' ni + +reduceCCompoundBlockItem + :: (MonadReduce Lab m) + => C.CCompoundBlockItem C.NodeInfo + -> (Context -> m [C.CCompoundBlockItem C.NodeInfo]) + -> Context + -> m [C.CCompoundBlockItem C.NodeInfo] +reduceCCompoundBlockItem r cont ctx = do + case r of + C.CBlockStmt smt -> do + case reduceCStatement smt ctx of + Just rsmt -> split ("remove statement", C.posOf r) (cont ctx) do + smt' <- rsmt + case smt' of + C.CCompound [] ss _ -> do + split ("expand compound statment", C.posOf r) ((ss <>) <$> cont ctx) do + (C.CBlockStmt smt' :) <$> cont ctx + _ow -> do + (C.CBlockStmt smt' :) <$> cont ctx + Nothing -> cont ctx + C.CBlockDecl declr -> do + case declr of + C.CDecl rec decl ni' -> do + (decl', ctx') <- foldr reduceCDeclarationItem (pure ([], ctx)) decl + case decl' of + [] + | AllowEmptyDeclarations `isIn` ctx' -> + split ("remove empty declaration", C.posOf r) (cont ctx') do + (C.CBlockDecl (C.CDecl rec decl' ni') :) <$> cont ctx' + | otherwise -> cont ctx' + _ow -> (C.CBlockDecl (C.CDecl rec decl' ni') :) <$> cont ctx' + d -> don'tHandle d + a -> don'tHandle a reduceCDeclarationItem - :: (CM m) + :: (MonadReduce Lab m) => C.CDeclarationItem C.NodeInfo - -> m ([C.CDeclarationItem C.NodeInfo], m a) - -> m ([C.CDeclarationItem C.NodeInfo], m a) + -> m ([C.CDeclarationItem C.NodeInfo], Context) + -> m ([C.CDeclarationItem C.NodeInfo], Context) reduceCDeclarationItem d ma = case d of C.CDeclarationItem - (C.CDeclr (Just i) [] Nothing [] ni) - (Just (C.CInitExpr c _)) + dr@(C.CDeclr (Just i) [] Nothing [] ni) + (Just (C.CInitExpr c ni')) Nothing -> do - (ds, cont) <- ma + (ds, ctx) <- ma + c' <- fromMaybe (pure zeroExpr) (reduceCExpr c ctx) split ("inline variable " <> C.identToString i, C.posOf ni) - (pure (ds, local (addInlineExpr i c) cont)) - (pure (d : ds, local (addInlineExpr i (C.CVar i ni)) cont)) + (pure (ds, addInlineExpr i c' ctx)) + ( pure + ( C.CDeclarationItem dr (Just (C.CInitExpr c' ni')) Nothing : ds + , addInlineExpr i (C.CVar i ni) ctx + ) + ) + C.CDeclarationItem (C.CDeclr (Just i) [] Nothing [] ni) Nothing Nothing -> do + (ds, ctx) <- ma + split + ("remove variable " <> C.identToString i, C.posOf ni) + (pure (ds, ctx)) + (pure (d : ds, addInlineExpr i (C.CVar i ni) ctx)) a -> don'tHandle a -prettyIdent :: C.Identifier C.NodeInfo -> [Char] -prettyIdent (C.Ident s _ a) = s ++ " at " ++ show (C.posOfNode a) - -instance CReducible C.CFunDef where - reduceC r = do - C.CFunDef spc dec cdecls smt ni <- inlineTypeDefs r - smt' <- reduceC smt - pure $ C.CFunDef spc dec cdecls smt' ni - -reduceCCompoundBlockItem - :: (CM m) - => C.CCompoundBlockItem C.NodeInfo - -> m [C.CCompoundBlockItem C.NodeInfo] - -> m [C.CCompoundBlockItem C.NodeInfo] -reduceCCompoundBlockItem r cont = case r of - C.CBlockStmt smt -> do - split ("remove statement", C.posOf r) cont do - smt' <- reduceC smt - (C.CBlockStmt smt' :) <$> cont - C.CBlockDecl declr -> do - case declr of - C.CDecl rec decl ni' -> do - (decl', cont') <- foldr reduceCDeclarationItem (pure ([], cont)) decl - allow <- keyword AllowEmptyDeclarations - case decl' of - [] - | allow -> - split ("remove empty declaration", C.posOf r) cont' do - (C.CBlockDecl (C.CDecl rec decl' ni') :) <$> cont' - | otherwise -> cont' - _ow -> (C.CBlockDecl (C.CDecl rec decl' ni') :) <$> cont' +reduceCStatementOrEmptyBlock + :: (MonadReduce Lab m) + => C.CStatement C.NodeInfo + -> Context + -> m (C.CStatement C.NodeInfo) +reduceCStatementOrEmptyBlock stmt ctx = do + case reduceCStatement stmt ctx of + Just ex -> do + ex + Nothing -> do + pure emptyBlock + where + emptyBlock = C.CCompound [] [] C.undefNode + +reduceCStatement + :: (MonadReduce Lab m) + => C.CStatement C.NodeInfo + -> Context + -> Maybe (m (C.CStatement C.NodeInfo)) +reduceCStatement smt ctx = case smt of + C.CCompound is cbi ni -> Just do + cbi' <- foldr reduceCCompoundBlockItem (\_ -> pure []) cbi ctx + pure $ C.CCompound is cbi' ni + C.CWhile e s dow ni -> do + rs <- reduceCStatement s ctx + Just do + e' <- reduceCExprOrZero e ctx + s' <- rs + pure $ C.CWhile e' s' dow ni + C.CExpr me ni -> do + case me of + Just e -> do + if DoNoops `isIn` ctx + then Just do + e' <- maybeSplit ("change to noop", C.posOf smt) $ reduceCExpr e ctx + pure $ C.CExpr e' ni + else do + re <- reduceCExpr e ctx + Just do + e' <- re + pure $ C.CExpr (Just e') ni + Nothing -> + Just $ pure $ C.CExpr Nothing ni + C.CReturn me ni -> Just do + case me of + Just e -> do + e' <- reduceCExprOrZero e ctx + pure $ C.CReturn (Just e') ni + Nothing -> + pure $ C.CReturn Nothing ni + C.CIf e s els ni -> Just do + e' <- maybeSplit ("remove condition", C.posOf e) $ reduceCExpr e ctx + els' <- case els of + Just els' -> do + maybeSplit ("remove else branch", C.posOf els') do + reduceCStatement els' ctx + Nothing -> pure Nothing + s' <- reduceCStatementOrEmptyBlock s ctx + case (e', els') of + (Nothing, Nothing) -> pure s' + (Just e'', Nothing) -> pure $ C.CIf e'' s' Nothing ni + (Nothing, Just x) -> pure $ C.CIf zeroExpr s' (Just x) ni + (Just e'', Just x) -> pure $ C.CIf e'' s' (Just x) ni + C.CFor e1 e2 e3 s ni -> Just $ do + (me1', ctx') <- case e1 of + C.CForDecl (C.CDecl rec decl ni') -> do + (decl', ctx') <- foldr reduceCDeclarationItem (pure ([], ctx)) decl + res <- + if null decl' + then + whenSplit + (AllowEmptyDeclarations `isIn` ctx') + ("remove empty declaration", C.posOf ni') + (pure Nothing) + (pure $ Just $ C.CForDecl (C.CDecl rec decl' ni')) + else pure $ Just $ C.CForDecl (C.CDecl rec decl' ni') + pure (res, ctx') + C.CForInitializing e -> + whenSplit + (AllowEmptyDeclarations `isIn` ctx) + ("remove empty declaration", C.posOf ni) + (pure (Nothing, ctx)) + (pure (Just $ C.CForInitializing e, ctx)) d -> don'tHandle d - a -> don'tHandle a -instance CReducible (C.CStatement C.NodeInfo) where - reduceC smt = case smt of - C.CCompound is cbi ni -> do - cbi' <- foldr reduceCCompoundBlockItem (pure []) cbi - pure $ C.CCompound is cbi' ni - C.CWhile e s dow ni -> do - e' <- reduceCExprOrZero e - s' <- reduceC s - pure $ C.CWhile e' s' dow ni - C.CExpr me ni -> do - case me of - Just e -> - splitOn DoNoops ("change to noop", C.posOf smt) (pure $ C.CExpr Nothing ni) do - e' <- reduceC e - pure $ C.CExpr (Just e') ni - Nothing -> - pure $ C.CExpr Nothing ni - C.CReturn me ni -> - case me of - Just e -> do - e' <- reduceCExprOrZero e - pure $ C.CReturn (Just e') ni - Nothing -> - pure $ C.CReturn Nothing ni - a -> don'tHandle a + s' <- reduceCStatementOrEmptyBlock s ctx' + case me1' of + Nothing -> do + split ("remove the for loop", C.posOf smt) (pure s') do + e2' <- case e2 of + Just e2' -> maybeSplit ("remove check", C.posOf e2') (reduceCExpr e2' ctx') + Nothing -> pure Nothing + e3' <- case e3 of + Just e3' -> maybeSplit ("remove iterator", C.posOf e3') (reduceCExpr e3' ctx') + Nothing -> pure Nothing + pure $ C.CFor (C.CForInitializing Nothing) e2' e3' s' ni + Just e1' -> do + e2' <- case e2 of + Just e2' -> maybeSplit ("remove check", C.posOf e2') (reduceCExpr e2' ctx') + Nothing -> pure Nothing + e3' <- case e3 of + Just e3' -> maybeSplit ("remove iterator", C.posOf e3') (reduceCExpr e3' ctx') + Nothing -> pure Nothing + pure $ C.CFor e1' e2' e3' s' ni + C.CBreak ni -> Just do + pure (C.CBreak ni) + C.CLabel i s [] ni -> Just do + s' <- reduceCStatementOrEmptyBlock s ctx + pure $ C.CLabel i s' [] ni + C.CGoto i ni -> Just do + pure $ C.CGoto i ni + a -> don'tHandle a -- C.CCompound is cbi ni -> do -- cbi' <- collect (reduce @C.CCompoundBlockItem) cbi @@ -196,29 +335,9 @@ instance CReducible (C.CStatement C.NodeInfo) where -- e' <- liftMaybe e -- reduce @C.CExpression e' -- pure $ C.CExpr e' ni --- C.CIf e s els ni -> do --- s' <- reduce s --- e' <- optional do --- reduce @C.CExpression e --- els' <- optional do --- els' <- liftMaybe els --- given >> reduce els' --- case (e', els') of --- (Nothing, Nothing) -> pure s' --- (Just e'', Nothing) -> pure $ C.CIf e'' s' Nothing ni --- (Nothing, Just x) -> pure $ C.CIf zeroExp s' (Just x) ni --- (Just e'', Just x) -> pure $ C.CIf e'' s' (Just x) ni --- C.CFor e1 e2 e3 s ni -> do --- reduce s <| do --- e1' <- reduce @C.CForInit e1 --- e2' <- optional $ liftMaybe e2 >>= reduce @C.CExpression --- e3' <- optional $ liftMaybe e3 >>= reduce @C.CExpression --- s' <- reduce s --- pure $ C.CFor e1' e2' e3' s' ni -- C.CReturn e ni -> do -- e' <- traverse (fmap orZero reduce) e -- pure $ C.CReturn e' ni --- C.CBreak ni -> pure (C.CBreak ni) -- C.CCont ni -> pure (C.CCont ni) -- C.CLabel i s [] ni -> do -- -- todo fix attrs @@ -226,42 +345,79 @@ instance CReducible (C.CStatement C.NodeInfo) where -- withFallback s' do -- givenThat (Val.is i) -- pure $ C.CLabel i s' [] ni --- C.CGoto i ni -> --- withFallback (C.CExpr Nothing ni) do --- givenThat (Val.is i) --- pure $ C.CGoto i ni -- C.CWhile e s dow ni -> do -- e' <- orZero (reduce @C.CExpression e) -- s' <- reduce s -- pure $ C.CWhile e' s' dow ni +-- | If the condition is statisfied try to reduce to the a. +whenSplit :: (MonadReduce Lab m) => Bool -> Lab -> m a -> m a -> m a +whenSplit cn lab a b + | cn = split lab a b + | otherwise = b + +maybeSplit :: (MonadReduce Lab m) => Lab -> Maybe (m a) -> m (Maybe a) +maybeSplit lab = \case + Just r -> do + split lab (pure Nothing) (Just <$> r) + Nothing -> do + pure Nothing + zeroExpr :: C.CExpression C.NodeInfo zeroExpr = C.CConst (C.CIntConst (C.cInteger 0) C.undefNode) -reduceCExprOrZero :: (CM m) => C.CExpr -> m C.CExpr -reduceCExprOrZero expr = - splitOn NoSemantics ("replace by zero", C.posOf expr) (pure zeroExpr) do - reduceC expr - -instance CReducible C.CExpr where - reduceC expr = case expr of - C.CBinary o elhs erhs ni -> - splitOn NoSemantics ("reduce to left", C.posOf elhs) (reduceC elhs) do - splitOn NoSemantics ("reduce to right", C.posOf erhs) (reduceC erhs) do - elhs' <- reduceC elhs - erhs' <- reduceC erhs - pure $ C.CBinary o elhs' erhs' ni - C.CVar i _ -> do - asks (Map.lookup i . inlineExprs) >>= \case - Just mx -> pure mx - Nothing -> fail ("Could not find " <> show i) - C.CConst x -> do - pure $ C.CConst x - C.CUnary o elhs ni -> do - elhs' <- reduceC elhs - splitOn NoSemantics ("reduce to operant", C.posOf expr) (pure elhs') do - pure $ C.CUnary o elhs' ni - a -> error (show a) +reduceCExprOrZero :: (MonadReduce Lab m) => C.CExpr -> Context -> m C.CExpr +reduceCExprOrZero expr ctx = do + case reduceCExpr expr ctx of + Just ex -> do + split ("replace by zero", C.posOf expr) (pure zeroExpr) ex + Nothing -> do + pure zeroExpr + +reduceCExpr :: (MonadReduce Lab m) => C.CExpr -> Context -> Maybe (m C.CExpr) +reduceCExpr expr ctx = case expr of + C.CBinary o elhs erhs ni -> do + case reduceCExpr elhs ctx of + Just elhs' -> case reduceCExpr erhs ctx of + Just erhs' -> pure do + split ("reduce to left", C.posOf elhs) elhs' do + split ("reduce to right", C.posOf erhs) erhs' do + l' <- elhs' + r' <- erhs' + pure $ C.CBinary o l' r' ni + Nothing -> + fail "could not reduce right hand side" + Nothing + | otherwise -> fail "could not reduce left hand side" + C.CAssign o elhs erhs ni -> + case reduceCExpr elhs (addKeyword DisallowVariableInlining ctx) of + Just elhs' -> case reduceCExpr erhs ctx of + Just erhs' -> pure do + split ("reduce to left", C.posOf elhs) elhs' do + split ("reduce to right", C.posOf erhs) erhs' do + l' <- elhs' + r' <- erhs' + pure $ C.CAssign o l' r' ni + Nothing -> + fail "could not reduce right hand side" + Nothing + | otherwise -> fail "could not reduce left hand side" + C.CVar i _ -> + case Map.lookup i . inlineExprs $ ctx of + Just mx -> case mx of + C.CVar _ _ -> pure (pure mx) + _ + | DisallowVariableInlining `isIn` ctx -> Nothing + | otherwise -> pure (pure mx) + Nothing -> fail ("Could not find " <> show i) + C.CConst x -> Just do + pure $ C.CConst x + C.CUnary o elhs ni -> do + elhs' <- reduceCExpr elhs (addKeyword DisallowVariableInlining ctx) + Just $ split ("reduce to operant", C.posOf expr) elhs' do + e <- elhs' + pure $ C.CUnary o e ni + a -> error (show a) -- C.CCall e es ni -> do -- e' <- reduce e @@ -287,8 +443,6 @@ instance CReducible C.CExpr where -- cd' <- reduce @C.CDeclaration cd -- e' <- reduce e -- pure $ C.CCast cd' e' ni --- C.CAssign op e1 e2 ni -> onBothExpr e1 e2 \e1' e2' -> --- pure $ C.CAssign op e1' e2' ni -- C.CIndex e1 e2 ni -> do -- e1' <- reduce e1 -- e2' <- orZero (reduce e2) @@ -303,29 +457,58 @@ instance CReducible C.CExpr where -- where -- onBothExpr elhs erhs = onBoth (reduce elhs) (reduce erhs) -splitIf :: (MonadReduce l m) => Bool -> l -> m a -> m a -> m a -splitIf True s a b = split s a b -splitIf False _ _ b = b - -splitOn :: (MonadReduce l m, MonadReader Context m) => Keyword -> l -> m a -> m a -> m a -splitOn k s a b = do - con <- keyword k - splitIf con s a b - -inlineTypeDefs :: forall d m. (Data d, MonadFail m, MonadReader Context m) => d -> m d -inlineTypeDefs r = do +-- splitIf :: (MonadReduce l m) => Bool -> l -> m a -> m a -> m a +-- splitIf True s a b = split s a b +-- splitIf False _ _ b = b +-- +-- splitOn :: (MonadReduce l m, MonadReader Context m) => Keyword -> l -> m a -> m a -> m a +-- splitOn k s a b = do +-- con <- keyword k +-- splitIf con s a b +-- +-- maybeSplit +-- :: (MonadReduce l m) +-- => l +-- -> Maybe (m a) +-- -> Maybe (m a) +-- -> Maybe (m a) +-- maybeSplit s a b = case a of +-- Just a' -> case b of +-- Just b' -> Just do +-- split s a' b' +-- Nothing -> Just a' +-- Nothing -> b +-- +-- maybeSplitOn +-- :: (MonadReduce l m) +-- => Keyword +-- -> l +-- -> ReaderT Context Maybe (m a) +-- -> ReaderT Context Maybe (m a) +-- -> ReaderT Context Maybe (m a) +-- maybeSplitOn k s a b = do +-- con <- keyword k +-- if con +-- then b +-- else ReaderT \ctx -> +-- case runReaderT a ctx of +-- Just a' -> case runReaderT b ctx of +-- Just b' -> Just $ split s a' b' +-- Nothing -> Just a' +-- Nothing -> runReaderT b ctx + +inlineTypeDefs :: forall d. (Data d) => d -> Context -> d +inlineTypeDefs r ctx = do case eqT @d @[C.CDeclarationSpecifier C.NodeInfo] of - Just Refl -> do - res' :: [[C.CDeclarationSpecifier C.NodeInfo]] <- forM r \case + Just Refl -> + r & concatMap \case C.CTypeSpec (C.CTypeDef idx _) -> do - res <- asks (Map.lookup idx . typeDefs) - case res of - Just args -> pure args - Nothing -> fail ("could not find typedef:" <> show idx) - a -> pure [a] - pure (fold res') + case Map.lookup idx . typeDefs $ ctx of + Just args -> args + Nothing -> error ("could not find typedef:" <> show idx) + a -> [a] Nothing -> - gmapM inlineTypeDefs r + gmapT (`inlineTypeDefs` ctx) r -- instance CReducible C.CExtDecl where -- reduceC (C.CFunDef spc dec cdecls smt ni) = do @@ -340,10 +523,10 @@ functionName :: C.CFunctionDef C.NodeInfo -> Maybe C.Ident functionName = \case C.CFunDef _ (C.CDeclr ix _ _ _ _) _ _ _ -> ix -isMain :: C.CFunctionDef C.NodeInfo -> Bool -isMain (C.CFunDef _ (C.CDeclr (Just i) _ _ _ _) _ _ _) = - C.identToString i == "main" -isMain _ow = False +-- isMain :: C.CFunctionDef C.NodeInfo -> Bool +-- isMain (C.CFunDef _ (C.CDeclr (Just i) _ _ _ _) _ _ _) = +-- C.identToString i == "main" +-- isMain _ow = False don'tHandle :: (HasCallStack, Functor f, Show (f ())) => f C.NodeInfo -> b don'tHandle f = error (show (f $> ())) @@ -548,6 +731,7 @@ don'tHandle f = error (show (f $> ())) -- (Just e'', Just x) -> pure $ C.CIf e'' s' (Just x) ni -- C.CFor e1 e2 e3 s ni -> do -- reduce s <| do +-- -- e1' <- reduce @C.CForInit e1 -- e2' <- optional $ liftMaybe e2 >>= reduce @C.CExpression -- e3' <- optional $ liftMaybe e3 >>= reduce @C.CExpression diff --git a/rtree-c/test/cases/large/llvm-26760.c b/rtree-c/test/cases/large/llvm-26760.c new file mode 100644 index 0000000..de54286 --- /dev/null +++ b/rtree-c/test/cases/large/llvm-26760.c @@ -0,0 +1,28 @@ +// From https://dl.acm.org/doi/pdf/10.1145/3586049 +typedef signed int8_t; +typedef short int16_t; +typedef int int32_t; +typedef unsigned uint32_t; +int8_t g_100; +int16_t func_33() { +int8_t l_790; +int32_t l_919 = 0x24F96B7BL; +uint32_t l_1052; + if (l_790) + for (;;) + break; + else for (; l_919; --l_919); + int32_t l_1081 = 1L; + int32_t B4o4obl_919 = l_919; + int8_t B4o4ocg_100 = g_100; + int32_t B4o4odl_1369 = B4o4ocg_100; + uint32_t B4o4ofl_1433 = B4o4odl_1369; + LABEL_4o4og:; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } + } + int main() {} diff --git a/rtree-c/test/cases/constant.c b/rtree-c/test/cases/small/constant.c similarity index 100% rename from rtree-c/test/cases/constant.c rename to rtree-c/test/cases/small/constant.c diff --git a/rtree-c/test/cases/main.c b/rtree-c/test/cases/small/main.c similarity index 100% rename from rtree-c/test/cases/main.c rename to rtree-c/test/cases/small/main.c diff --git a/rtree-c/test/cases/typedef.c b/rtree-c/test/cases/small/typedef.c similarity index 100% rename from rtree-c/test/cases/typedef.c rename to rtree-c/test/cases/small/typedef.c diff --git a/rtree-c/test/cases/while-loops.c b/rtree-c/test/cases/small/while-loops.c similarity index 100% rename from rtree-c/test/cases/while-loops.c rename to rtree-c/test/cases/small/while-loops.c diff --git a/rtree-c/test/expected/constant/reduction/r000.c b/rtree-c/test/expected/constant/reduction/r000.c deleted file mode 100644 index 2d97bcf..0000000 --- a/rtree-c/test/expected/constant/reduction/r000.c +++ /dev/null @@ -1,6 +0,0 @@ -int x = 10; -int main() -{ - int y = 25; - return x + y; -} diff --git a/rtree-c/test/expected/constant/reduction/r000.choices b/rtree-c/test/expected/constant/reduction/r000.choices deleted file mode 100644 index 805d1e4..0000000 --- a/rtree-c/test/expected/constant/reduction/r000.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/constant.c": line 5) -0 inline variable y at ("test/cases/constant.c": line 4) -0 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r000000.c b/rtree-c/test/expected/constant/reduction/r000000.c new file mode 100644 index 0000000..8caa6b7 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r000000.c @@ -0,0 +1,13 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 0 reduce to right at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + int y = 25; + return x + y; +} diff --git a/rtree-c/test/expected/constant/reduction/r000001.c b/rtree-c/test/expected/constant/reduction/r000001.c new file mode 100644 index 0000000..c237e98 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r000001.c @@ -0,0 +1,13 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 1 reduce to right at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + int y = 25; + return y; +} diff --git a/rtree-c/test/expected/constant/reduction/r00001.c b/rtree-c/test/expected/constant/reduction/r00001.c new file mode 100644 index 0000000..093aea2 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r00001.c @@ -0,0 +1,12 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 1 reduce to left at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + int y = 25; + return x; +} diff --git a/rtree-c/test/expected/constant/reduction/r0001.c b/rtree-c/test/expected/constant/reduction/r0001.c new file mode 100644 index 0000000..2ab76f4 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0001.c @@ -0,0 +1,11 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 1 replace by zero at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + int y = 25; + return 0; +} diff --git a/rtree-c/test/expected/constant/reduction/r001.c b/rtree-c/test/expected/constant/reduction/r001.c index ce017c7..5f2d262 100644 --- a/rtree-c/test/expected/constant/reduction/r001.c +++ b/rtree-c/test/expected/constant/reduction/r001.c @@ -1,3 +1,7 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 1 remove statement at ("test/cases/small/constant.c": line 5) + int x = 10; int main() { diff --git a/rtree-c/test/expected/constant/reduction/r001.choices b/rtree-c/test/expected/constant/reduction/r001.choices deleted file mode 100644 index ac41d35..0000000 --- a/rtree-c/test/expected/constant/reduction/r001.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/constant.c": line 5) -0 inline variable y at ("test/cases/constant.c": line 4) -0 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r010.c b/rtree-c/test/expected/constant/reduction/r010.c deleted file mode 100644 index c9d30b9..0000000 --- a/rtree-c/test/expected/constant/reduction/r010.c +++ /dev/null @@ -1,5 +0,0 @@ -int x = 10; -int main() -{ - return x + 25; -} diff --git a/rtree-c/test/expected/constant/reduction/r010.choices b/rtree-c/test/expected/constant/reduction/r010.choices deleted file mode 100644 index f19a549..0000000 --- a/rtree-c/test/expected/constant/reduction/r010.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/constant.c": line 5) -1 inline variable y at ("test/cases/constant.c": line 4) -0 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r010000.c b/rtree-c/test/expected/constant/reduction/r010000.c new file mode 100644 index 0000000..9db7e67 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r010000.c @@ -0,0 +1,12 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 0 reduce to right at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + return x + 25; +} diff --git a/rtree-c/test/expected/constant/reduction/r010001.c b/rtree-c/test/expected/constant/reduction/r010001.c new file mode 100644 index 0000000..8e50811 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r010001.c @@ -0,0 +1,12 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 1 reduce to right at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + return 25; +} diff --git a/rtree-c/test/expected/constant/reduction/r01001.c b/rtree-c/test/expected/constant/reduction/r01001.c new file mode 100644 index 0000000..2a5899b --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r01001.c @@ -0,0 +1,11 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 1 reduce to left at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + return x; +} diff --git a/rtree-c/test/expected/constant/reduction/r0101.c b/rtree-c/test/expected/constant/reduction/r0101.c new file mode 100644 index 0000000..611d6f1 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0101.c @@ -0,0 +1,10 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 1 replace by zero at ("test/cases/small/constant.c": line 5) + +int x = 10; +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/constant/reduction/r011.c b/rtree-c/test/expected/constant/reduction/r011.c index 78bfe21..08fb77e 100644 --- a/rtree-c/test/expected/constant/reduction/r011.c +++ b/rtree-c/test/expected/constant/reduction/r011.c @@ -1,3 +1,7 @@ +// 0 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 1 remove statement at ("test/cases/small/constant.c": line 5) + int x = 10; int main() { diff --git a/rtree-c/test/expected/constant/reduction/r011.choices b/rtree-c/test/expected/constant/reduction/r011.choices deleted file mode 100644 index 22358a3..0000000 --- a/rtree-c/test/expected/constant/reduction/r011.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/constant.c": line 5) -1 inline variable y at ("test/cases/constant.c": line 4) -0 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r100.c b/rtree-c/test/expected/constant/reduction/r100.c deleted file mode 100644 index 1c93710..0000000 --- a/rtree-c/test/expected/constant/reduction/r100.c +++ /dev/null @@ -1,5 +0,0 @@ -int main() -{ - int y = 25; - return 10 + y; -} diff --git a/rtree-c/test/expected/constant/reduction/r100.choices b/rtree-c/test/expected/constant/reduction/r100.choices deleted file mode 100644 index 2bc5629..0000000 --- a/rtree-c/test/expected/constant/reduction/r100.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/constant.c": line 5) -0 inline variable y at ("test/cases/constant.c": line 4) -1 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r100000.c b/rtree-c/test/expected/constant/reduction/r100000.c new file mode 100644 index 0000000..55eec85 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r100000.c @@ -0,0 +1,12 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 0 reduce to right at ("test/cases/small/constant.c": line 5) + +int main() +{ + int y = 25; + return 10 + y; +} diff --git a/rtree-c/test/expected/constant/reduction/r100001.c b/rtree-c/test/expected/constant/reduction/r100001.c new file mode 100644 index 0000000..5b53020 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r100001.c @@ -0,0 +1,12 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 1 reduce to right at ("test/cases/small/constant.c": line 5) + +int main() +{ + int y = 25; + return y; +} diff --git a/rtree-c/test/expected/constant/reduction/r10001.c b/rtree-c/test/expected/constant/reduction/r10001.c new file mode 100644 index 0000000..24353b7 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r10001.c @@ -0,0 +1,11 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 1 reduce to left at ("test/cases/small/constant.c": line 5) + +int main() +{ + int y = 25; + return 10; +} diff --git a/rtree-c/test/expected/constant/reduction/r1001.c b/rtree-c/test/expected/constant/reduction/r1001.c new file mode 100644 index 0000000..36ad940 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1001.c @@ -0,0 +1,10 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 1 replace by zero at ("test/cases/small/constant.c": line 5) + +int main() +{ + int y = 25; + return 0; +} diff --git a/rtree-c/test/expected/constant/reduction/r101.c b/rtree-c/test/expected/constant/reduction/r101.c index b673765..9cd3655 100644 --- a/rtree-c/test/expected/constant/reduction/r101.c +++ b/rtree-c/test/expected/constant/reduction/r101.c @@ -1,3 +1,7 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 0 inline variable y at ("test/cases/small/constant.c": line 4) +// 1 remove statement at ("test/cases/small/constant.c": line 5) + int main() { int y = 25; diff --git a/rtree-c/test/expected/constant/reduction/r101.choices b/rtree-c/test/expected/constant/reduction/r101.choices deleted file mode 100644 index e49e1e4..0000000 --- a/rtree-c/test/expected/constant/reduction/r101.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/constant.c": line 5) -0 inline variable y at ("test/cases/constant.c": line 4) -1 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r110.c b/rtree-c/test/expected/constant/reduction/r110.c deleted file mode 100644 index fd039c7..0000000 --- a/rtree-c/test/expected/constant/reduction/r110.c +++ /dev/null @@ -1,4 +0,0 @@ -int main() -{ - return 10 + 25; -} diff --git a/rtree-c/test/expected/constant/reduction/r110.choices b/rtree-c/test/expected/constant/reduction/r110.choices deleted file mode 100644 index f84f675..0000000 --- a/rtree-c/test/expected/constant/reduction/r110.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/constant.c": line 5) -1 inline variable y at ("test/cases/constant.c": line 4) -1 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/constant/reduction/r110000.c b/rtree-c/test/expected/constant/reduction/r110000.c new file mode 100644 index 0000000..8b8d961 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r110000.c @@ -0,0 +1,11 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 0 reduce to right at ("test/cases/small/constant.c": line 5) + +int main() +{ + return 10 + 25; +} diff --git a/rtree-c/test/expected/constant/reduction/r110001.c b/rtree-c/test/expected/constant/reduction/r110001.c new file mode 100644 index 0000000..3546559 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r110001.c @@ -0,0 +1,11 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 0 reduce to left at ("test/cases/small/constant.c": line 5) +// 1 reduce to right at ("test/cases/small/constant.c": line 5) + +int main() +{ + return 25; +} diff --git a/rtree-c/test/expected/constant/reduction/r11001.c b/rtree-c/test/expected/constant/reduction/r11001.c new file mode 100644 index 0000000..7d0aad4 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r11001.c @@ -0,0 +1,10 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 0 replace by zero at ("test/cases/small/constant.c": line 5) +// 1 reduce to left at ("test/cases/small/constant.c": line 5) + +int main() +{ + return 10; +} diff --git a/rtree-c/test/expected/constant/reduction/r1101.c b/rtree-c/test/expected/constant/reduction/r1101.c new file mode 100644 index 0000000..43237b2 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1101.c @@ -0,0 +1,9 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 0 remove statement at ("test/cases/small/constant.c": line 5) +// 1 replace by zero at ("test/cases/small/constant.c": line 5) + +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/constant/reduction/r111.c b/rtree-c/test/expected/constant/reduction/r111.c index 5047a34..217608d 100644 --- a/rtree-c/test/expected/constant/reduction/r111.c +++ b/rtree-c/test/expected/constant/reduction/r111.c @@ -1,3 +1,7 @@ +// 1 inline variable x at ("test/cases/small/constant.c": line 1) +// 1 inline variable y at ("test/cases/small/constant.c": line 4) +// 1 remove statement at ("test/cases/small/constant.c": line 5) + int main() { } diff --git a/rtree-c/test/expected/constant/reduction/r111.choices b/rtree-c/test/expected/constant/reduction/r111.choices deleted file mode 100644 index e0fb7c2..0000000 --- a/rtree-c/test/expected/constant/reduction/r111.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/constant.c": line 5) -1 inline variable y at ("test/cases/constant.c": line 4) -1 inline variable x at ("test/cases/constant.c": line 1) diff --git a/rtree-c/test/expected/llvm-26760/main.c b/rtree-c/test/expected/llvm-26760/main.c new file mode 100644 index 0000000..e77cad7 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/main.c @@ -0,0 +1,34 @@ +typedef signed int8_t; +typedef short int16_t; +typedef int int32_t; +typedef unsigned uint32_t; +int8_t g_100; +int16_t func_33() +{ + int8_t l_790; + int32_t l_919 = 0x24f96b7bL; + uint32_t l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int32_t l_1081 = 1L; + int32_t B4o4obl_919 = l_919; + int8_t B4o4ocg_100 = g_100; + int32_t B4o4odl_1369 = B4o4ocg_100; + uint32_t B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r1.c b/rtree-c/test/expected/llvm-26760/reduction/r1.c new file mode 100644 index 0000000..e9387cf --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r1.c @@ -0,0 +1,71 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 0 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 0 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 0 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 0 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +typedef short int16_t; +typedef int int32_t; +typedef unsigned uint32_t; +signed g_100; +int16_t func_33() +{ + signed l_790; + int32_t l_919 = 0x24f96b7bL; + uint32_t l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int32_t l_1081 = 1L; + int32_t B4o4obl_919 = l_919; + signed B4o4ocg_100 = g_100; + int32_t B4o4odl_1369 = B4o4ocg_100; + uint32_t B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r11.c b/rtree-c/test/expected/llvm-26760/reduction/r11.c new file mode 100644 index 0000000..bcdfc62 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r11.c @@ -0,0 +1,70 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 0 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 0 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 0 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +typedef int int32_t; +typedef unsigned uint32_t; +signed g_100; +short func_33() +{ + signed l_790; + int32_t l_919 = 0x24f96b7bL; + uint32_t l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int32_t l_1081 = 1L; + int32_t B4o4obl_919 = l_919; + signed B4o4ocg_100 = g_100; + int32_t B4o4odl_1369 = B4o4ocg_100; + uint32_t B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r111.c b/rtree-c/test/expected/llvm-26760/reduction/r111.c new file mode 100644 index 0000000..ef2edec --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r111.c @@ -0,0 +1,69 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 0 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 0 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +typedef unsigned uint32_t; +signed g_100; +short func_33() +{ + signed l_790; + int l_919 = 0x24f96b7bL; + uint32_t l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int l_1081 = 1L; + int B4o4obl_919 = l_919; + signed B4o4ocg_100 = g_100; + int B4o4odl_1369 = B4o4ocg_100; + uint32_t B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r1111.c b/rtree-c/test/expected/llvm-26760/reduction/r1111.c new file mode 100644 index 0000000..40acd24 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r1111.c @@ -0,0 +1,68 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 0 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +signed g_100; +short func_33() +{ + signed l_790; + int l_919 = 0x24f96b7bL; + unsigned l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int l_1081 = 1L; + int B4o4obl_919 = l_919; + signed B4o4ocg_100 = g_100; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r11111.c b/rtree-c/test/expected/llvm-26760/reduction/r11111.c new file mode 100644 index 0000000..6bfa176 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r11111.c @@ -0,0 +1,67 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +short func_33() +{ + signed l_790; + int l_919 = 0x24f96b7bL; + unsigned l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int l_1081 = 1L; + int B4o4obl_919 = l_919; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r111110.c b/rtree-c/test/expected/llvm-26760/reduction/r111110.c new file mode 100644 index 0000000..6bfa176 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r111110.c @@ -0,0 +1,67 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 0 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 22) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 22) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove condition at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) + +short func_33() +{ + signed l_790; + int l_919 = 0x24f96b7bL; + unsigned l_1052; + if (l_790) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int l_1081 = 1L; + int B4o4obl_919 = l_919; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + l_790 = B4o4ofl_1433; + if (l_790) + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r1111101.c b/rtree-c/test/expected/llvm-26760/reduction/r1111101.c new file mode 100644 index 0000000..5dfd603 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r1111101.c @@ -0,0 +1,60 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 1 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 0 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove iterator at ("test/cases/large/llvm-26760.c": line 14) +// 0 reduce to operant at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) +// 0 expand compound statment at ("test/cases/large/llvm-26760.c": line 23) + +short func_33() +{ + int l_919 = 0x24f96b7bL; + unsigned l_1052; + if (0) + for (;;) + break; + else + for (; l_919; --l_919) + ; + int l_1081 = 1L; + int B4o4obl_919 = l_919; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r11111011.c b/rtree-c/test/expected/llvm-26760/reduction/r11111011.c new file mode 100644 index 0000000..2102127 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r11111011.c @@ -0,0 +1,57 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 1 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 1 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 0 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 21) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 21) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to left at ("test/cases/large/llvm-26760.c": line 24) +// 0 reduce to right at ("test/cases/large/llvm-26760.c": line 24) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) +// 0 expand compound statment at ("test/cases/large/llvm-26760.c": line 23) + +short func_33() +{ + unsigned l_1052; + if (0) + for (;;) + break; + else + for (; 0x24f96b7bL;) + ; + int l_1081 = 1L; + int B4o4obl_919 = 0x24f96b7bL; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + l_1052 = l_1052 >> l_1081; + { + l_1052 = l_1052 << B4o4obl_919; + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r111110111.c b/rtree-c/test/expected/llvm-26760/reduction/r111110111.c new file mode 100644 index 0000000..2abf141 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r111110111.c @@ -0,0 +1,44 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 1 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 1 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 1 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 remove else branch at ("test/cases/large/llvm-26760.c": line 14) +// 0 remove check at ("test/cases/large/llvm-26760.c": line 14) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) +// 0 expand compound statment at ("test/cases/large/llvm-26760.c": line 23) + +short func_33() +{ + if (0) + for (;;) + break; + else + for (; 0x24f96b7bL;) + ; + int l_1081 = 1L; + int B4o4obl_919 = 0x24f96b7bL; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + { + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/llvm-26760/reduction/r1111101111.c b/rtree-c/test/expected/llvm-26760/reduction/r1111101111.c new file mode 100644 index 0000000..14d2b6c --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/r1111101111.c @@ -0,0 +1,36 @@ +// 1 inline typedef int8_t at ("test/cases/large/llvm-26760.c": line 2) +// 1 inline typedef int16_t at ("test/cases/large/llvm-26760.c": line 3) +// 1 inline typedef int32_t at ("test/cases/large/llvm-26760.c": line 4) +// 1 inline typedef uint32_t at ("test/cases/large/llvm-26760.c": line 5) +// 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +// 0 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +// 1 remove variable l_790 at ("test/cases/large/llvm-26760.c": line 8) +// 1 inline variable l_919 at ("test/cases/large/llvm-26760.c": line 9) +// 1 remove variable l_1052 at ("test/cases/large/llvm-26760.c": line 10) +// 1 remove statement at ("test/cases/large/llvm-26760.c": line 11) +// 0 inline variable l_1081 at ("test/cases/large/llvm-26760.c": line 15) +// 0 inline variable B4o4obl_919 at ("test/cases/large/llvm-26760.c": line 16) +// 0 inline variable B4o4ocg_100 at ("test/cases/large/llvm-26760.c": line 17) +// 0 inline variable B4o4odl_1369 at ("test/cases/large/llvm-26760.c": line 18) +// 0 inline variable B4o4ofl_1433 at ("test/cases/large/llvm-26760.c": line 19) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 20) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 23) +// 0 remove statement at ("test/cases/large/llvm-26760.c": line 25) +// 0 expand compound statment at ("test/cases/large/llvm-26760.c": line 23) + +short func_33() +{ + int l_1081 = 1L; + int B4o4obl_919 = 0x24f96b7bL; + signed B4o4ocg_100 = 0; + int B4o4odl_1369 = B4o4ocg_100; + unsigned B4o4ofl_1433 = B4o4odl_1369; +LABEL_4o4og: + ; + { + goto LABEL_4o4og; + } +} +int main() +{ +} diff --git a/rtree-c/test/expected/main/reduction/r.c b/rtree-c/test/expected/main/reduction/r.c index 5047a34..d3a1f6a 100644 --- a/rtree-c/test/expected/main/reduction/r.c +++ b/rtree-c/test/expected/main/reduction/r.c @@ -1,3 +1,4 @@ + int main() { } diff --git a/rtree-c/test/expected/main/reduction/r.choices b/rtree-c/test/expected/main/reduction/r.choices deleted file mode 100644 index e69de29..0000000 diff --git a/rtree-c/test/expected/typedef/reduction/r0000.c b/rtree-c/test/expected/typedef/reduction/r0000.c deleted file mode 100644 index 2d12abf..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0000.c +++ /dev/null @@ -1,9 +0,0 @@ -typedef int uint64; -void f(uint64 a) -{ -} -int main() -{ - uint64 x = 1; - return x; -} diff --git a/rtree-c/test/expected/typedef/reduction/r0000.choices b/rtree-c/test/expected/typedef/reduction/r0000.choices deleted file mode 100644 index fa1b06c..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0000.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r00000.c b/rtree-c/test/expected/typedef/reduction/r00000.c new file mode 100644 index 0000000..49b6840 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00000.c @@ -0,0 +1,15 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ + uint64 x = 1; + return x; +} diff --git a/rtree-c/test/expected/typedef/reduction/r00001.c b/rtree-c/test/expected/typedef/reduction/r00001.c new file mode 100644 index 0000000..b72e671 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00001.c @@ -0,0 +1,15 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ + uint64 x = 1; + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r0001.c b/rtree-c/test/expected/typedef/reduction/r0001.c index b7888ce..67c85a8 100644 --- a/rtree-c/test/expected/typedef/reduction/r0001.c +++ b/rtree-c/test/expected/typedef/reduction/r0001.c @@ -1,3 +1,8 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + typedef int uint64; void f(uint64 a) { diff --git a/rtree-c/test/expected/typedef/reduction/r0001.choices b/rtree-c/test/expected/typedef/reduction/r0001.choices deleted file mode 100644 index 9c6d7a2..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0001.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r0010.c b/rtree-c/test/expected/typedef/reduction/r0010.c deleted file mode 100644 index d13fa76..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0010.c +++ /dev/null @@ -1,8 +0,0 @@ -typedef int uint64; -void f(uint64 a) -{ -} -int main() -{ - return 1; -} diff --git a/rtree-c/test/expected/typedef/reduction/r0010.choices b/rtree-c/test/expected/typedef/reduction/r0010.choices deleted file mode 100644 index 986dac1..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0010.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r00100.c b/rtree-c/test/expected/typedef/reduction/r00100.c new file mode 100644 index 0000000..4f85f50 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00100.c @@ -0,0 +1,14 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ + return 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r00101.c b/rtree-c/test/expected/typedef/reduction/r00101.c new file mode 100644 index 0000000..a6a5e5a --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00101.c @@ -0,0 +1,14 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r0011.c b/rtree-c/test/expected/typedef/reduction/r0011.c index 1ce0a1b..21a4e7c 100644 --- a/rtree-c/test/expected/typedef/reduction/r0011.c +++ b/rtree-c/test/expected/typedef/reduction/r0011.c @@ -1,3 +1,8 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + typedef int uint64; void f(uint64 a) { diff --git a/rtree-c/test/expected/typedef/reduction/r0011.choices b/rtree-c/test/expected/typedef/reduction/r0011.choices deleted file mode 100644 index 81989ef..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0011.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r0100.c b/rtree-c/test/expected/typedef/reduction/r0100.c deleted file mode 100644 index e187d43..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0100.c +++ /dev/null @@ -1,6 +0,0 @@ -typedef int uint64; -int main() -{ - uint64 x = 1; - return x; -} diff --git a/rtree-c/test/expected/typedef/reduction/r0100.choices b/rtree-c/test/expected/typedef/reduction/r0100.choices deleted file mode 100644 index 145e4f8..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0100.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r01000.c b/rtree-c/test/expected/typedef/reduction/r01000.c new file mode 100644 index 0000000..f722eb5 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01000.c @@ -0,0 +1,12 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +int main() +{ + uint64 x = 1; + return x; +} diff --git a/rtree-c/test/expected/typedef/reduction/r01001.c b/rtree-c/test/expected/typedef/reduction/r01001.c new file mode 100644 index 0000000..7b14af1 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01001.c @@ -0,0 +1,12 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +int main() +{ + uint64 x = 1; + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r0101.c b/rtree-c/test/expected/typedef/reduction/r0101.c index 1ab8fec..9b6f3ac 100644 --- a/rtree-c/test/expected/typedef/reduction/r0101.c +++ b/rtree-c/test/expected/typedef/reduction/r0101.c @@ -1,3 +1,8 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + typedef int uint64; int main() { diff --git a/rtree-c/test/expected/typedef/reduction/r0101.choices b/rtree-c/test/expected/typedef/reduction/r0101.choices deleted file mode 100644 index 0bda8fb..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0101.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r0110.c b/rtree-c/test/expected/typedef/reduction/r0110.c deleted file mode 100644 index 239f38d..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0110.c +++ /dev/null @@ -1,5 +0,0 @@ -typedef int uint64; -int main() -{ - return 1; -} diff --git a/rtree-c/test/expected/typedef/reduction/r0110.choices b/rtree-c/test/expected/typedef/reduction/r0110.choices deleted file mode 100644 index 8f09241..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0110.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r01100.c b/rtree-c/test/expected/typedef/reduction/r01100.c new file mode 100644 index 0000000..cd02f33 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01100.c @@ -0,0 +1,11 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +int main() +{ + return 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r01101.c b/rtree-c/test/expected/typedef/reduction/r01101.c new file mode 100644 index 0000000..7e19176 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01101.c @@ -0,0 +1,11 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r0111.c b/rtree-c/test/expected/typedef/reduction/r0111.c index 17825b9..997cfee 100644 --- a/rtree-c/test/expected/typedef/reduction/r0111.c +++ b/rtree-c/test/expected/typedef/reduction/r0111.c @@ -1,3 +1,8 @@ +// 0 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + typedef int uint64; int main() { diff --git a/rtree-c/test/expected/typedef/reduction/r0111.choices b/rtree-c/test/expected/typedef/reduction/r0111.choices deleted file mode 100644 index 291f387..0000000 --- a/rtree-c/test/expected/typedef/reduction/r0111.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -0 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r1000.c b/rtree-c/test/expected/typedef/reduction/r1000.c deleted file mode 100644 index 3ec3f43..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1000.c +++ /dev/null @@ -1,8 +0,0 @@ -void f(int a) -{ -} -int main() -{ - int x = 1; - return x; -} diff --git a/rtree-c/test/expected/typedef/reduction/r1000.choices b/rtree-c/test/expected/typedef/reduction/r1000.choices deleted file mode 100644 index a7a7a50..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1000.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r10000.c b/rtree-c/test/expected/typedef/reduction/r10000.c new file mode 100644 index 0000000..f5985fa --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r10000.c @@ -0,0 +1,14 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +void f(int a) +{ +} +int main() +{ + int x = 1; + return x; +} diff --git a/rtree-c/test/expected/typedef/reduction/r10001.c b/rtree-c/test/expected/typedef/reduction/r10001.c new file mode 100644 index 0000000..d93fe3f --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r10001.c @@ -0,0 +1,14 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +void f(int a) +{ +} +int main() +{ + int x = 1; + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r1001.c b/rtree-c/test/expected/typedef/reduction/r1001.c index 975eaa4..3849e3b 100644 --- a/rtree-c/test/expected/typedef/reduction/r1001.c +++ b/rtree-c/test/expected/typedef/reduction/r1001.c @@ -1,3 +1,8 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + void f(int a) { } diff --git a/rtree-c/test/expected/typedef/reduction/r1001.choices b/rtree-c/test/expected/typedef/reduction/r1001.choices deleted file mode 100644 index d8280cc..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1001.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r1010.c b/rtree-c/test/expected/typedef/reduction/r1010.c deleted file mode 100644 index e11fc7d..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1010.c +++ /dev/null @@ -1,7 +0,0 @@ -void f(int a) -{ -} -int main() -{ - return 1; -} diff --git a/rtree-c/test/expected/typedef/reduction/r1010.choices b/rtree-c/test/expected/typedef/reduction/r1010.choices deleted file mode 100644 index 4b158a3..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1010.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r10100.c b/rtree-c/test/expected/typedef/reduction/r10100.c new file mode 100644 index 0000000..270bbf6 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r10100.c @@ -0,0 +1,13 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +void f(int a) +{ +} +int main() +{ + return 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r10101.c b/rtree-c/test/expected/typedef/reduction/r10101.c new file mode 100644 index 0000000..4ed1e92 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r10101.c @@ -0,0 +1,13 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +void f(int a) +{ +} +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r1011.c b/rtree-c/test/expected/typedef/reduction/r1011.c index 3fa6be1..8f9fdd9 100644 --- a/rtree-c/test/expected/typedef/reduction/r1011.c +++ b/rtree-c/test/expected/typedef/reduction/r1011.c @@ -1,3 +1,8 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + void f(int a) { } diff --git a/rtree-c/test/expected/typedef/reduction/r1011.choices b/rtree-c/test/expected/typedef/reduction/r1011.choices deleted file mode 100644 index 76cb6f2..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1011.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -0 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r1100.c b/rtree-c/test/expected/typedef/reduction/r1100.c deleted file mode 100644 index 2eb1833..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1100.c +++ /dev/null @@ -1,5 +0,0 @@ -int main() -{ - int x = 1; - return x; -} diff --git a/rtree-c/test/expected/typedef/reduction/r1100.choices b/rtree-c/test/expected/typedef/reduction/r1100.choices deleted file mode 100644 index 9ee0fbd..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1100.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r11000.c b/rtree-c/test/expected/typedef/reduction/r11000.c new file mode 100644 index 0000000..748f367 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r11000.c @@ -0,0 +1,11 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +int main() +{ + int x = 1; + return x; +} diff --git a/rtree-c/test/expected/typedef/reduction/r11001.c b/rtree-c/test/expected/typedef/reduction/r11001.c new file mode 100644 index 0000000..b93d545 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r11001.c @@ -0,0 +1,11 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +int main() +{ + int x = 1; + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r1101.c b/rtree-c/test/expected/typedef/reduction/r1101.c index a382e8e..168a46e 100644 --- a/rtree-c/test/expected/typedef/reduction/r1101.c +++ b/rtree-c/test/expected/typedef/reduction/r1101.c @@ -1,3 +1,8 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + int main() { int x = 1; diff --git a/rtree-c/test/expected/typedef/reduction/r1101.choices b/rtree-c/test/expected/typedef/reduction/r1101.choices deleted file mode 100644 index 1e5ebac..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1101.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -0 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r1110.c b/rtree-c/test/expected/typedef/reduction/r1110.c deleted file mode 100644 index 2227c3a..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1110.c +++ /dev/null @@ -1,4 +0,0 @@ -int main() -{ - return 1; -} diff --git a/rtree-c/test/expected/typedef/reduction/r1110.choices b/rtree-c/test/expected/typedef/reduction/r1110.choices deleted file mode 100644 index 2b83126..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1110.choices +++ /dev/null @@ -1,4 +0,0 @@ -0 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/typedef/reduction/r11100.c b/rtree-c/test/expected/typedef/reduction/r11100.c new file mode 100644 index 0000000..388eb72 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r11100.c @@ -0,0 +1,10 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 0 replace by zero at ("test/cases/small/typedef.c": line 9) + +int main() +{ + return 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r11101.c b/rtree-c/test/expected/typedef/reduction/r11101.c new file mode 100644 index 0000000..69a9641 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r11101.c @@ -0,0 +1,10 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove statement at ("test/cases/small/typedef.c": line 9) +// 1 replace by zero at ("test/cases/small/typedef.c": line 9) + +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/typedef/reduction/r1111.c b/rtree-c/test/expected/typedef/reduction/r1111.c index 5047a34..345a4fc 100644 --- a/rtree-c/test/expected/typedef/reduction/r1111.c +++ b/rtree-c/test/expected/typedef/reduction/r1111.c @@ -1,3 +1,8 @@ +// 1 inline typedef uint64 at ("test/cases/small/typedef.c": line 2) +// 1 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove statement at ("test/cases/small/typedef.c": line 9) + int main() { } diff --git a/rtree-c/test/expected/typedef/reduction/r1111.choices b/rtree-c/test/expected/typedef/reduction/r1111.choices deleted file mode 100644 index 6c02b12..0000000 --- a/rtree-c/test/expected/typedef/reduction/r1111.choices +++ /dev/null @@ -1,4 +0,0 @@ -1 remove statement at ("test/cases/typedef.c": line 9) -1 inline variable x at ("test/cases/typedef.c": line 8) -1 remove function f at ("test/cases/typedef.c": line 4) -1 inline typedef uint64 at ("test/cases/typedef.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r000.c b/rtree-c/test/expected/while-loops/reduction/r000.c deleted file mode 100644 index cf4c537..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r000.c +++ /dev/null @@ -1,8 +0,0 @@ -int main() -{ - int i = 0; - while (i < 10) - { - i++; - } -} diff --git a/rtree-c/test/expected/while-loops/reduction/r000.choices b/rtree-c/test/expected/while-loops/reduction/r000.choices deleted file mode 100644 index 7712d43..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r000.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/while-loops.c": line 4) -0 remove statement at ("test/cases/while-loops.c": line 3) -0 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r0000000.c b/rtree-c/test/expected/while-loops/reduction/r0000000.c new file mode 100644 index 0000000..6d5db5e --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0000000.c @@ -0,0 +1,16 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 0 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i < 10) + { + i++; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0000001.c b/rtree-c/test/expected/while-loops/reduction/r0000001.c new file mode 100644 index 0000000..71df2ce --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0000001.c @@ -0,0 +1,16 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 1 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i < 10) + { + i; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r000001.c b/rtree-c/test/expected/while-loops/reduction/r000001.c new file mode 100644 index 0000000..6633e53 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r000001.c @@ -0,0 +1,14 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 1 remove statement at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i < 10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0000100.c b/rtree-c/test/expected/while-loops/reduction/r0000100.c new file mode 100644 index 0000000..139e84f --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0000100.c @@ -0,0 +1,16 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 0 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (10) + { + i++; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0000101.c b/rtree-c/test/expected/while-loops/reduction/r0000101.c new file mode 100644 index 0000000..8786ab8 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0000101.c @@ -0,0 +1,16 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 1 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (10) + { + i; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r000011.c b/rtree-c/test/expected/while-loops/reduction/r000011.c new file mode 100644 index 0000000..f7d5579 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r000011.c @@ -0,0 +1,14 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to right at ("test/cases/small/while-loops.c": line 3) +// 1 remove statement at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r000100.c b/rtree-c/test/expected/while-loops/reduction/r000100.c new file mode 100644 index 0000000..b524fca --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r000100.c @@ -0,0 +1,15 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 0 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i) + { + i++; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r000101.c b/rtree-c/test/expected/while-loops/reduction/r000101.c new file mode 100644 index 0000000..b077238 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r000101.c @@ -0,0 +1,15 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 1 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i) + { + i; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r00011.c b/rtree-c/test/expected/while-loops/reduction/r00011.c new file mode 100644 index 0000000..3aa141b --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r00011.c @@ -0,0 +1,13 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 1 remove statement at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (i) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r001.c b/rtree-c/test/expected/while-loops/reduction/r001.c deleted file mode 100644 index 714143b..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r001.c +++ /dev/null @@ -1,7 +0,0 @@ -int main() -{ - int i = 0; - while (i < 10) - { - } -} diff --git a/rtree-c/test/expected/while-loops/reduction/r001.choices b/rtree-c/test/expected/while-loops/reduction/r001.choices deleted file mode 100644 index f04eb97..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r001.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/while-loops.c": line 4) -0 remove statement at ("test/cases/while-loops.c": line 3) -0 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r00100.c b/rtree-c/test/expected/while-loops/reduction/r00100.c new file mode 100644 index 0000000..65d31d9 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r00100.c @@ -0,0 +1,14 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 1 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 0 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (0) + { + i++; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r00101.c b/rtree-c/test/expected/while-loops/reduction/r00101.c new file mode 100644 index 0000000..e8e3166 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r00101.c @@ -0,0 +1,14 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 1 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 remove statement at ("test/cases/small/while-loops.c": line 4) +// 1 reduce to operant at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (0) + { + i; + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0011.c b/rtree-c/test/expected/while-loops/reduction/r0011.c new file mode 100644 index 0000000..7e6f1ef --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0011.c @@ -0,0 +1,12 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 1 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 1 remove statement at ("test/cases/small/while-loops.c": line 4) + +int main() +{ + int i = 0; + while (0) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r01.c b/rtree-c/test/expected/while-loops/reduction/r01.c index 28c5719..be67234 100644 --- a/rtree-c/test/expected/while-loops/reduction/r01.c +++ b/rtree-c/test/expected/while-loops/reduction/r01.c @@ -1,3 +1,6 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove statement at ("test/cases/small/while-loops.c": line 3) + int main() { int i = 0; diff --git a/rtree-c/test/expected/while-loops/reduction/r01.choices b/rtree-c/test/expected/while-loops/reduction/r01.choices deleted file mode 100644 index a891b77..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r01.choices +++ /dev/null @@ -1,2 +0,0 @@ -1 remove statement at ("test/cases/while-loops.c": line 3) -0 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r100.c b/rtree-c/test/expected/while-loops/reduction/r100.c deleted file mode 100644 index 45b4b7d..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r100.c +++ /dev/null @@ -1,7 +0,0 @@ -int main() -{ - while (0 < 10) - { - 0++; - } -} diff --git a/rtree-c/test/expected/while-loops/reduction/r100.choices b/rtree-c/test/expected/while-loops/reduction/r100.choices deleted file mode 100644 index cdd24cf..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r100.choices +++ /dev/null @@ -1,3 +0,0 @@ -0 remove statement at ("test/cases/while-loops.c": line 4) -0 remove statement at ("test/cases/while-loops.c": line 3) -1 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r10000.c b/rtree-c/test/expected/while-loops/reduction/r10000.c new file mode 100644 index 0000000..3a753f8 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r10000.c @@ -0,0 +1,12 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to right at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + while (0 < 10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r10001.c b/rtree-c/test/expected/while-loops/reduction/r10001.c new file mode 100644 index 0000000..ad2c9b2 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r10001.c @@ -0,0 +1,12 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 0 reduce to left at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to right at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + while (10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r1001.c b/rtree-c/test/expected/while-loops/reduction/r1001.c new file mode 100644 index 0000000..3aa47a9 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r1001.c @@ -0,0 +1,11 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) +// 1 reduce to left at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + while (0) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r101.c b/rtree-c/test/expected/while-loops/reduction/r101.c index db783f8..d8796c6 100644 --- a/rtree-c/test/expected/while-loops/reduction/r101.c +++ b/rtree-c/test/expected/while-loops/reduction/r101.c @@ -1,6 +1,10 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove statement at ("test/cases/small/while-loops.c": line 3) +// 1 replace by zero at ("test/cases/small/while-loops.c": line 3) + int main() { - while (0 < 10) + while (0) { } } diff --git a/rtree-c/test/expected/while-loops/reduction/r101.choices b/rtree-c/test/expected/while-loops/reduction/r101.choices deleted file mode 100644 index c054f9b..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r101.choices +++ /dev/null @@ -1,3 +0,0 @@ -1 remove statement at ("test/cases/while-loops.c": line 4) -0 remove statement at ("test/cases/while-loops.c": line 3) -1 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/expected/while-loops/reduction/r11.c b/rtree-c/test/expected/while-loops/reduction/r11.c index 5047a34..57635b6 100644 --- a/rtree-c/test/expected/while-loops/reduction/r11.c +++ b/rtree-c/test/expected/while-loops/reduction/r11.c @@ -1,3 +1,6 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove statement at ("test/cases/small/while-loops.c": line 3) + int main() { } diff --git a/rtree-c/test/expected/while-loops/reduction/r11.choices b/rtree-c/test/expected/while-loops/reduction/r11.choices deleted file mode 100644 index 7ad5e3f..0000000 --- a/rtree-c/test/expected/while-loops/reduction/r11.choices +++ /dev/null @@ -1,2 +0,0 @@ -1 remove statement at ("test/cases/while-loops.c": line 3) -1 inline variable i at ("test/cases/while-loops.c": line 2) diff --git a/rtree-c/test/src/ReduceCSpec.hs b/rtree-c/test/src/ReduceCSpec.hs index f447df9..7ae8327 100644 --- a/rtree-c/test/src/ReduceCSpec.hs +++ b/rtree-c/test/src/ReduceCSpec.hs @@ -17,10 +17,12 @@ import Test.Hspec.Glitter import qualified Language.C as C import qualified Text.PrettyPrint as P +import qualified Control.Monad.IRTree as IRTree import Control.Monad.RTree (extract, iinputs, probe) import Data.Bool import Data.Functor import Data.RPath +import Data.String import qualified Language.C.System.GCC as C import ReduceC import System.Directory.Internal.Prelude (tryIOError) @@ -28,10 +30,15 @@ import System.Process.Typed spec :: Spec spec = do - cases <- runIO (listDirectory "test/cases") + specSmallCases + specLargeCases + +specLargeCases :: Spec +specLargeCases = do + cases <- runIO (listDirectory "test/cases/large") forM_ cases \cname -> do - let cfrom = "test/cases" </> cname + let cfrom = "test/cases/large" </> cname describe cfrom do c <- runIO $ parse cfrom @@ -48,24 +55,55 @@ spec = do describe "reduction" do it "should extract itself" do - fmap ($> ()) (extract $ defaultReduceC c) `shouldBe` Just (c $> ()) + 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 - forM_ (iinputs (defaultReduceC c)) \(i, c') -> do + forM_ (iinputs (defaultReduceC c)) \(i, _) -> 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 - ) + renderWithChoices rfile (probe (defaultReduceC c) i) ) do it "should validate all reductions" . mapM_ $ \a -> do @@ -89,6 +127,24 @@ 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" + ) + parse :: FilePath -> IO C.CTranslUnit parse cfrom = do cf <- C.parseCFile (C.newGCC "clang") Nothing [] cfrom -- GitLab