diff --git a/rtree-c/src/ReduceC.hs b/rtree-c/src/ReduceC.hs index 288b0e53619007d2fec60b921551f18c116676c4..59c991968c2f99dc93c04f48460eabfceb16c907 100644 --- a/rtree-c/src/ReduceC.hs +++ b/rtree-c/src/ReduceC.hs @@ -53,8 +53,7 @@ data Context = Context { keywords :: !(Set.Set Keyword) , typeDefs :: !(Map.Map C.Ident (CType, InlineType)) , inlineExprs :: !(Map.Map C.Ident InlineExpr) - , fields :: !(Map.Map C.Ident (Maybe C.Ident)) - , structs :: !(Map.Map C.Ident (Maybe C.CStructUnion)) + , structs :: !(Map.Map C.Ident InlineStruct) } deriving (Show) @@ -63,6 +62,11 @@ data InlineType | ITInline ![C.CDeclarationSpecifier C.NodeInfo] deriving (Show, Eq) +data InlineStruct + = ISDelete + | ISKeep + deriving (Show, Eq) + data InlineExpr = IEDelete | IEInline !C.CExpr @@ -111,19 +115,10 @@ addKeyword k Context{..} = , .. } -addStruct :: StructDef -> Context -> Context -addStruct (StructDef k fs _) Context{..} = - Context - { structs = Map.insert k Nothing structs - , fields = foldr (`Map.insert` Just k) fields fs - , .. - } - -removeStruct :: StructDef -> Context -> Context -removeStruct (StructDef k fs un) Context{..} = +addInlineStruct :: C.Ident -> InlineStruct -> Context -> Context +addInlineStruct k is Context{..} = Context - { structs = Map.insert k (Just un) structs - , fields = foldr (`Map.insert` Nothing) fields fs + { structs = Map.insert k is structs , .. } @@ -139,7 +134,6 @@ defaultContext = , (C.builtinIdent "__PRETTY_FUNCTION__", IEKeep CTInt) , (C.builtinIdent "__FUNCTION__", IEKeep CTInt) ] - , fields = Map.empty , structs = Map.empty } @@ -320,14 +314,17 @@ reduceParams' ctx declrs = do C.CFunDeclr (C.CFunParamsNew decls i) j k -> do (unzip -> (decls', defs)) <- decls & mapM \case - C.CDecl def items l -> do + a@(C.CDecl def items l) -> do (unzip -> (items', defs)) <- items & mapM \case a'@(C.CDeclarationItem (C.CDeclr idx _ _ _ _) _ _) -> - split - ("remove parameter", C.posOf k) - (pure ([], [(Nothing, idx)])) - (pure ([a'], [(Just (ctype ctx def), idx)])) + if shouldDeleteDeclaration ctx a + then pure ([], [(Nothing, idx)]) + else + split + ("remove parameter", C.posOf k) + (pure ([], [(Nothing, idx)])) + (pure ([a'], [(Just (ctype ctx def), idx)])) a' -> notSupportedYet a' k case concat items' of [] -> pure ([], concat defs) @@ -430,8 +427,15 @@ handleDecl d ctx = case inlineTypeDefsCDeclaration d ctx of (pure (Nothing, addTypeDefs [ids] (ctype ctx rst, ITInline rst) ctx)) (pure (Just (pure d), addTypeDefs [ids] (ctype ctx rst, ITKeep) ctx)) -- A const - C.CDecl spc decl ni' -> do - (decl', ctx') <- foldr (reduceCDeclarationItem (ctype ctx spc)) (pure ([], ctx)) decl + d'@(C.CDecl spc decl ni') -> do + (decl', ctx') <- + foldr + ( reduceCDeclarationItem + (shouldDeleteDeclaration ctx d') + (ctype ctx spc) + ) + (pure ([], ctx)) + decl let fn = do spc1 <- trySplit ("remove static", C.posOf ni') spc $ filter \case C.CStorageSpec (C.CStatic _) -> False @@ -446,56 +450,63 @@ handleDecl d ctx = case inlineTypeDefsCDeclaration d ctx of ([], stcts) -> split ("remove declaration", C.posOf d) - (pure (Nothing, foldr removeStruct ctx' stcts)) + (pure (Nothing, foldr (\(StructDef k _ _) -> addInlineStruct k ISDelete) ctx' stcts)) do - pure (Just fn, foldr addStruct ctx' stcts) + pure (Just fn, foldr (\(StructDef k _ _) -> addInlineStruct k ISKeep) ctx' stcts) (_, stcts) -> - pure (Just fn, foldr addStruct ctx' stcts) + pure (Just fn, foldr (\(StructDef k _ _) -> addInlineStruct k ISKeep) ctx' stcts) a -> don'tHandleWithPos a reduceCDeclarationItem :: (MonadReduce Lab m) - => CType + => Bool + -> CType -> C.CDeclarationItem C.NodeInfo -> m ([C.CDeclarationItem C.NodeInfo], Context) -> m ([C.CDeclarationItem C.NodeInfo], Context) -reduceCDeclarationItem t d ma = case d of +reduceCDeclarationItem shouldDelete t d ma = case d of C.CDeclarationItem dr@(C.CDeclr (Just i) [] Nothing [] ni) (Just (C.CInitExpr c ni')) Nothing -> do (ds, ctx) <- ma c' <- fromMaybe (pure zeroExpr) (reduceCExpr c ctx) - split - ("inline variable " <> C.identToString i, C.posOf ni) - (pure (ds, addInlineExpr i (IEInline c') ctx)) - ( pure - ( inlineTypeDefsCDI (C.CDeclarationItem dr (Just (C.CInitExpr c' ni')) Nothing) ctx - : ds - , addInlineExpr i (IEKeep t) ctx + if shouldDelete + then pure (ds, addInlineExpr i (IEInline c') ctx) + else + split + ("inline variable " <> C.identToString i, C.posOf ni) + (pure (ds, addInlineExpr i (IEInline c') ctx)) + ( pure + ( inlineTypeDefsCDI (C.CDeclarationItem dr (Just (C.CInitExpr c' ni')) Nothing) ctx + : ds + , addInlineExpr i (IEKeep t) ctx + ) ) - ) C.CDeclarationItem (C.CDeclr (Just i) a Nothing b ni) ex Nothing -> do (ds, ctx) <- ma - ex' <- case ex of - Just ix -> maybeSplit ("remove initializer", C.posOf ni) (reduceCInitializer ix ctx) - Nothing -> pure Nothing - - (a', t') <- - if C.identToString i == "printf" - then pure (a, CTAny) - else do - (a', defs) <- reduceParams' ctx a - let t' = case defs of - [args] -> CTFun (map fst args) - [] -> t - _x -> error ("Unexpected" <> unlines (map show _x) <> show (C.posOf ni)) - pure (a', t') - let d' = C.CDeclarationItem (C.CDeclr (Just i) a' Nothing b ni) ex' Nothing - split - ("remove variable " <> C.identToString i, C.posOf ni) - (pure (ds, addInlineExpr i IEDelete ctx)) - (pure (inlineTypeDefsCDI d' ctx : ds, addInlineExpr i (IEKeep t') ctx)) + if shouldDelete + then pure (ds, addInlineExpr i IEDelete ctx) + else do + ex' <- case ex of + Just ix -> maybeSplit ("remove initializer", C.posOf ni) (reduceCInitializer ix ctx) + Nothing -> pure Nothing + + (a', t') <- + if C.identToString i == "printf" + then pure (a, CTAny) + else do + (a', defs) <- reduceParams' ctx a + let t' = case defs of + [args] -> CTFun (map fst args) + [] -> t + _x -> error ("Unexpected" <> unlines (map show _x) <> show (C.posOf ni)) + pure (a', t') + let d' = C.CDeclarationItem (C.CDeclr (Just i) a' Nothing b ni) ex' Nothing + split + ("remove variable " <> C.identToString i, C.posOf ni) + (pure (ds, addInlineExpr i IEDelete ctx)) + (pure (inlineTypeDefsCDI d' ctx : ds, addInlineExpr i (IEKeep t') ctx)) a@(C.CDeclarationItem (C.CDeclr _ _ _ _ ni) _ _) -> do don'tHandleWithNodeInfo a ni a -> don'tHandle a @@ -538,7 +549,9 @@ reduceCStatement smt labs ctx = case smt of C.CCompound is cbi ni -> do cbi' <- lift $ evalStateT (mapM (reduceCCompoundBlockItem labs) cbi) ctx case concat cbi' of - [] -> mzero + [] -> do + exceptIf ("remove empty compound", C.posOf smt) + pure (C.CCompound is [] ni) ccbi -> pure (C.CCompound is ccbi ni) C.CWhile e s dow ni -> do s' <- reduceCStatement s labs ctx @@ -586,8 +599,8 @@ reduceCStatement smt labs ctx = case smt of (Nothing, Just s', Nothing) -> pure s' C.CFor e1 e2 e3 s ni -> do (me1', ctx') <- case e1 of - C.CForDecl (C.CDecl rec decl ni') -> do - (decl', ctx') <- foldr (reduceCDeclarationItem (ctype ctx rec)) (pure ([], ctx)) decl + C.CForDecl d@(C.CDecl rec decl ni') -> do + (decl', ctx') <- foldr (reduceCDeclarationItem (shouldDeleteDeclaration ctx d) (ctype ctx rec)) (pure ([], ctx)) decl res <- if null decl' then @@ -609,12 +622,16 @@ reduceCStatement smt labs ctx = case smt of s' <- reduceCStatementOrEmptyBlock s labs ctx' let forloop n = 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 + e2' <- runMaybeT do + e2' <- liftMaybe e2 + re2' <- liftMaybe (reduceCExpr e2' ctx') + exceptIf ("remove check", C.posOf e2') + re2' + e3' <- runMaybeT do + e3' <- liftMaybe e3 + re3' <- liftMaybe (reduceCExpr e3' ctx') + exceptIf ("remove iterator", C.posOf e3') + re3' let e2'' = if AllowInfiniteForLoops `isIn` ctx || isNothing e2 then e2' @@ -850,6 +867,36 @@ inlineTypeDefsCDeclaration decl ctx = C.CDecl (inlineTypeDefsSpecs items ctx) (map (`inlineTypeDefsCDI` ctx) decli) ni a -> don'tHandle a +shouldDeleteDeclaration :: Context -> C.CDeclaration C.NodeInfo -> Bool +shouldDeleteDeclaration ctx decl = + case decl of + C.CDecl items decli _ -> any shouldDeleteDeclSpec items || any shouldDeleteDeclItem decli + a -> don'tHandle a + where + shouldDeleteDeclItem = \case + C.CDeclarationItem a _ _ -> shouldDeleteDeclartor a + a -> don'tHandle a + + shouldDeleteDeclartor = \case + C.CDeclr _ def _ _ _ -> any shouldDeleteDerivedDeclartor def + + shouldDeleteDerivedDeclartor = \case + C.CFunDeclr (C.CFunParamsNew x _) _ _ -> + any (shouldDeleteDeclaration ctx) x + C.CArrDeclr{} -> False + C.CPtrDeclr _ _ -> False + a -> don'tHandle a + + shouldDeleteDeclSpec = \case + C.CTypeSpec (C.CSUType (C.CStruct _ (Just idx) Nothing _ _) _) -> + case Map.lookup idx . structs $ ctx of + Just ISDelete -> True + Just ISKeep -> False + Nothing -> error ("could not find struct:" <> show idx) + C.CTypeSpec (C.CSUType (C.CStruct _ _ (Just c) _ _) _) -> + any (shouldDeleteDeclaration ctx) c + _ow -> False + inlineTypeDefsSpecs :: [C.CDeclarationSpecifier C.NodeInfo] -> Context -> [C.CDeclarationSpecifier C.NodeInfo] inlineTypeDefsSpecs r ctx = r & concatMap \case @@ -858,11 +905,11 @@ inlineTypeDefsSpecs r ctx = Just (_, ITKeep) -> [a] Just (_, ITInline res) -> res Nothing -> error ("could not find typedef:" <> show idx) - a@(C.CTypeSpec (C.CSUType (C.CStruct _ (Just idx) Nothing _ _) _)) -> - case Map.lookup idx . structs $ ctx of - Just (Just def) -> [C.CTypeSpec (C.CSUType def C.undefNode)] - Just Nothing -> [a] - Nothing -> error ("could not find struct:" <> show idx) + -- a@(C.CTypeSpec (C.CSUType (C.CStruct _ (Just idx) Nothing _ _) _)) -> + -- case Map.lookup idx . structs $ ctx of + -- Just (Just def) -> [C.CTypeSpec (C.CSUType def C.undefNode)] + -- Just Nothing -> [a] + -- Nothing -> error ("could not find struct:" <> show idx) C.CTypeSpec (C.CSUType (C.CStruct a b (Just c) d e) f) -> [C.CTypeSpec (C.CSUType (C.CStruct a b (Just $ map (`inlineTypeDefsCDeclaration` ctx) c) d e) f)] a -> [a] diff --git a/rtree-c/test/cases/small/structfn.c b/rtree-c/test/cases/small/structfn.c index f04d49c17ac2c3037820eb736b9317e7098131e3..2726d53f6f41ec1636bdc5e7ceeca1c9a2e4a424 100644 --- a/rtree-c/test/cases/small/structfn.c +++ b/rtree-c/test/cases/small/structfn.c @@ -1,4 +1,6 @@ struct S0 {}; -struct S0 g0 = {}; void fn(struct S0 a) {} -int main() { fn(g0); } +int main() { + struct S0 g0 = {}; + fn(g0); +} diff --git a/rtree-c/test/expected/add/reduction/r000000000.c.hs b/rtree-c/test/expected/add/reduction/r000000000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000000000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000000001.c.hs b/rtree-c/test/expected/add/reduction/r000000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000000001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000000010.c.hs b/rtree-c/test/expected/add/reduction/r000000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000000010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000000011.c.hs b/rtree-c/test/expected/add/reduction/r000000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000000011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0000001.c b/rtree-c/test/expected/add/reduction/r00000010.c similarity index 88% rename from rtree-c/test/expected/add/reduction/r0000001.c rename to rtree-c/test/expected/add/reduction/r00000010.c index 5ae5f93b9ac99aea4f830316adbf28071c30261c..a9b8bf009be5f5c976b7a7b40bf8925323ac0f88 100644 --- a/rtree-c/test/expected/add/reduction/r0000001.c +++ b/rtree-c/test/expected/add/reduction/r00000010.c @@ -5,6 +5,7 @@ // 0 reduce to left at ("test/cases/small/add.c": line 2) // 0 reduce to right at ("test/cases/small/add.c": line 2) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { diff --git a/rtree-c/test/expected/add/reduction/r00000010.c.hs b/rtree-c/test/expected/add/reduction/r00000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00000011.c b/rtree-c/test/expected/add/reduction/r00000011.c new file mode 100644 index 0000000000000000000000000000000000000000..24156152dd0a261be362e43db3b348da4316e404 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000011.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 2) +// 0 reduce to left at ("test/cases/small/add.c": line 2) +// 0 reduce to right at ("test/cases/small/add.c": line 2) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a, int b) +{ + return a + b; +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r00000011.c.hs b/rtree-c/test/expected/add/reduction/r00000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000001000.c.hs b/rtree-c/test/expected/add/reduction/r000001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000001000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000001001.c.hs b/rtree-c/test/expected/add/reduction/r000001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000001001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000001010.c.hs b/rtree-c/test/expected/add/reduction/r000001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000001010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000001011.c.hs b/rtree-c/test/expected/add/reduction/r000001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r000001011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0000011.c b/rtree-c/test/expected/add/reduction/r00000110.c similarity index 88% rename from rtree-c/test/expected/add/reduction/r0000011.c rename to rtree-c/test/expected/add/reduction/r00000110.c index eeaf7c27a0b3006230b67357b756fc6a40b1da3c..e46567f27e83ba6d09d5cd3fd015e397e9aa5a9d 100644 --- a/rtree-c/test/expected/add/reduction/r0000011.c +++ b/rtree-c/test/expected/add/reduction/r00000110.c @@ -5,6 +5,7 @@ // 0 reduce to left at ("test/cases/small/add.c": line 2) // 1 reduce to right at ("test/cases/small/add.c": line 2) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { diff --git a/rtree-c/test/expected/add/reduction/r00000110.c.hs b/rtree-c/test/expected/add/reduction/r00000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00000111.c b/rtree-c/test/expected/add/reduction/r00000111.c new file mode 100644 index 0000000000000000000000000000000000000000..263c1a84eeb535074e14236a96e5f0df976cf13d --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000111.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 2) +// 0 reduce to left at ("test/cases/small/add.c": line 2) +// 1 reduce to right at ("test/cases/small/add.c": line 2) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a, int b) +{ + return b; +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r00000111.c.hs b/rtree-c/test/expected/add/reduction/r00000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00000111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00001000.c.hs b/rtree-c/test/expected/add/reduction/r00001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00001000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00001001.c.hs b/rtree-c/test/expected/add/reduction/r00001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00001001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00001010.c.hs b/rtree-c/test/expected/add/reduction/r00001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00001010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00001011.c.hs b/rtree-c/test/expected/add/reduction/r00001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00001011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r000011.c b/rtree-c/test/expected/add/reduction/r0000110.c similarity index 86% rename from rtree-c/test/expected/add/reduction/r000011.c rename to rtree-c/test/expected/add/reduction/r0000110.c index 8eceedf9170bab2609277faadea0362837e5f9a4..ca3fe6c1ec501479aac77c5f1f92f05e146f602d 100644 --- a/rtree-c/test/expected/add/reduction/r000011.c +++ b/rtree-c/test/expected/add/reduction/r0000110.c @@ -4,6 +4,7 @@ // 0 remove return statement at ("test/cases/small/add.c": line 2) // 1 reduce to left at ("test/cases/small/add.c": line 2) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { diff --git a/rtree-c/test/expected/add/reduction/r0000110.c.hs b/rtree-c/test/expected/add/reduction/r0000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0000110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0000111.c b/rtree-c/test/expected/add/reduction/r0000111.c new file mode 100644 index 0000000000000000000000000000000000000000..8535f15fb69c46683859cededbb75f5eaf3969f4 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0000111.c @@ -0,0 +1,15 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 2) +// 1 reduce to left at ("test/cases/small/add.c": line 2) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a, int b) +{ + return a; +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r0000111.c.hs b/rtree-c/test/expected/add/reduction/r0000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0000111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0001000.c b/rtree-c/test/expected/add/reduction/r00010000.c similarity index 88% rename from rtree-c/test/expected/add/reduction/r0001000.c rename to rtree-c/test/expected/add/reduction/r00010000.c index 1360f67c4eeba39a9a778a9672cfdc942bb6d422..b7541f9fba731f64ee776322008a65321ec3f57e 100644 --- a/rtree-c/test/expected/add/reduction/r0001000.c +++ b/rtree-c/test/expected/add/reduction/r00010000.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 0 do without param at ("test/cases/small/add.c": line 6) // 0 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r00010000.c.hs b/rtree-c/test/expected/add/reduction/r00010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0001001.c b/rtree-c/test/expected/add/reduction/r00010001.c similarity index 88% rename from rtree-c/test/expected/add/reduction/r0001001.c rename to rtree-c/test/expected/add/reduction/r00010001.c index 6a86c10b194f07186a776c044a23e3652341d8fa..baf64fd8ef0a708ac6bdf7a11fadd13736408d23 100644 --- a/rtree-c/test/expected/add/reduction/r0001001.c +++ b/rtree-c/test/expected/add/reduction/r00010001.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 0 do without param at ("test/cases/small/add.c": line 6) // 1 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r00010001.c.hs b/rtree-c/test/expected/add/reduction/r00010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00010010.c b/rtree-c/test/expected/add/reduction/r00010010.c new file mode 100644 index 0000000000000000000000000000000000000000..4805450e2b42ec19f65033fcdf961cf68fd6d580 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010010.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(0, 23); +} diff --git a/rtree-c/test/expected/add/reduction/r00010010.c.hs b/rtree-c/test/expected/add/reduction/r00010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00010011.c b/rtree-c/test/expected/add/reduction/r00010011.c new file mode 100644 index 0000000000000000000000000000000000000000..fbbff2204386fc3286db0d0385d2f8d479faf64f --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010011.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(0, 0); +} diff --git a/rtree-c/test/expected/add/reduction/r00010011.c.hs b/rtree-c/test/expected/add/reduction/r00010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00010011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0001010.c b/rtree-c/test/expected/add/reduction/r0001010.c index 9627ccd0f42644295b1d09a76d8c1a89aa2d3e20..ee2d5802f43264e4caa7e9bf5f3ca72fa7f4b62e 100644 --- a/rtree-c/test/expected/add/reduction/r0001010.c +++ b/rtree-c/test/expected/add/reduction/r0001010.c @@ -2,14 +2,13 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) -// 0 remove return statement at ("test/cases/small/add.c": line 6) -// 1 do without param at ("test/cases/small/add.c": line 6) -// 0 do without param at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { } int main() { - return add(0, 23); } diff --git a/rtree-c/test/expected/add/reduction/r0001010.c.hs b/rtree-c/test/expected/add/reduction/r0001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0001010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0001011.c b/rtree-c/test/expected/add/reduction/r0001011.c index 2df413b4528f37abd5201cca36d4d06aaf924693..a8719bcca64a58e144de2c9b27d3c99d25c86be6 100644 --- a/rtree-c/test/expected/add/reduction/r0001011.c +++ b/rtree-c/test/expected/add/reduction/r0001011.c @@ -2,14 +2,13 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) -// 0 remove return statement at ("test/cases/small/add.c": line 6) -// 1 do without param at ("test/cases/small/add.c": line 6) -// 1 do without param at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { } int main() { - return add(0, 0); } diff --git a/rtree-c/test/expected/add/reduction/r0001011.c.hs b/rtree-c/test/expected/add/reduction/r0001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0001011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00011000.c b/rtree-c/test/expected/add/reduction/r00011000.c new file mode 100644 index 0000000000000000000000000000000000000000..e36826cfd70e4a76d2efb07928231214c1446882 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011000.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(10, 23); +} diff --git a/rtree-c/test/expected/add/reduction/r00011000.c.hs b/rtree-c/test/expected/add/reduction/r00011000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00011001.c b/rtree-c/test/expected/add/reduction/r00011001.c new file mode 100644 index 0000000000000000000000000000000000000000..665a0d2a39b49eeca5d4e5fec95cf3c0a2a9ecd5 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011001.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(10, 0); +} diff --git a/rtree-c/test/expected/add/reduction/r00011001.c.hs b/rtree-c/test/expected/add/reduction/r00011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00011010.c b/rtree-c/test/expected/add/reduction/r00011010.c new file mode 100644 index 0000000000000000000000000000000000000000..0c8e5b4b4eb08a2e9b1cb779e365e068416d6d81 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011010.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(0, 23); +} diff --git a/rtree-c/test/expected/add/reduction/r00011010.c.hs b/rtree-c/test/expected/add/reduction/r00011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00011011.c b/rtree-c/test/expected/add/reduction/r00011011.c new file mode 100644 index 0000000000000000000000000000000000000000..1bcb7b1ae9216207cfd2c9f83bd11aa68e6211fe --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011011.c @@ -0,0 +1,16 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) + +int add(int a, int b) +{ +} +int main() +{ + return add(0, 0); +} diff --git a/rtree-c/test/expected/add/reduction/r00011011.c.hs b/rtree-c/test/expected/add/reduction/r00011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r00011011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00011.c b/rtree-c/test/expected/add/reduction/r0001110.c similarity index 73% rename from rtree-c/test/expected/add/reduction/r00011.c rename to rtree-c/test/expected/add/reduction/r0001110.c index cfbfbc6cffc7b84eb3b52ee8f2aac5c4a2d0d5f1..a6c596eb3590b7a5d288587132526ddaba19dc4b 100644 --- a/rtree-c/test/expected/add/reduction/r00011.c +++ b/rtree-c/test/expected/add/reduction/r0001110.c @@ -2,7 +2,9 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a, int b) { diff --git a/rtree-c/test/expected/add/reduction/r0001110.c.hs b/rtree-c/test/expected/add/reduction/r0001110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0001110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0001111.c b/rtree-c/test/expected/add/reduction/r0001111.c new file mode 100644 index 0000000000000000000000000000000000000000..1112f98a956b57ebb31fc8759f99e707fa57a2de --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0001111.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a, int b) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r0001111.c.hs b/rtree-c/test/expected/add/reduction/r0001111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0001111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r001000.c.hs b/rtree-c/test/expected/add/reduction/r001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r001000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r001001.c.hs b/rtree-c/test/expected/add/reduction/r001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r001001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00101.c b/rtree-c/test/expected/add/reduction/r001010.c similarity index 84% rename from rtree-c/test/expected/add/reduction/r00101.c rename to rtree-c/test/expected/add/reduction/r001010.c index 0ee958d82e4847df04a0798554a3a185de909c6f..ebb9b3a19de0ecb2f577053a74946fe6e4c976c7 100644 --- a/rtree-c/test/expected/add/reduction/r00101.c +++ b/rtree-c/test/expected/add/reduction/r001010.c @@ -3,6 +3,7 @@ // 1 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 2) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a) { diff --git a/rtree-c/test/expected/add/reduction/r001010.c.hs b/rtree-c/test/expected/add/reduction/r001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r001010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r001011.c b/rtree-c/test/expected/add/reduction/r001011.c new file mode 100644 index 0000000000000000000000000000000000000000..1498fb3bab17819346d7ee4c46f06851e2074bc9 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r001011.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a) +{ + return a; +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r001011.c.hs b/rtree-c/test/expected/add/reduction/r001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r001011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r001100.c b/rtree-c/test/expected/add/reduction/r0011000.c similarity index 86% rename from rtree-c/test/expected/add/reduction/r001100.c rename to rtree-c/test/expected/add/reduction/r0011000.c index 8b1f24348f674a2620e006baf8ae62cf8492757c..a2306c0389a13454ffca0ad47f57771e427c347f 100644 --- a/rtree-c/test/expected/add/reduction/r001100.c +++ b/rtree-c/test/expected/add/reduction/r0011000.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 0 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r0011000.c.hs b/rtree-c/test/expected/add/reduction/r0011000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r001101.c b/rtree-c/test/expected/add/reduction/r0011001.c similarity index 86% rename from rtree-c/test/expected/add/reduction/r001101.c rename to rtree-c/test/expected/add/reduction/r0011001.c index aff561a12fc95f793138bf3f7b1068fb5a067a10..cd6a239aecc0fdedd6054720ad81307ebca28e88 100644 --- a/rtree-c/test/expected/add/reduction/r001101.c +++ b/rtree-c/test/expected/add/reduction/r0011001.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 1 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r0011001.c.hs b/rtree-c/test/expected/add/reduction/r0011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r00111.c b/rtree-c/test/expected/add/reduction/r0011010.c similarity index 73% rename from rtree-c/test/expected/add/reduction/r00111.c rename to rtree-c/test/expected/add/reduction/r0011010.c index 8d2fea121536d59a5493173c84ccde79aafe8bcc..d45ce349c07c427bd814f4eabb3bd8d3c46239e1 100644 --- a/rtree-c/test/expected/add/reduction/r00111.c +++ b/rtree-c/test/expected/add/reduction/r0011010.c @@ -2,7 +2,9 @@ // 0 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int a) { diff --git a/rtree-c/test/expected/add/reduction/r0011010.c.hs b/rtree-c/test/expected/add/reduction/r0011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0011011.c b/rtree-c/test/expected/add/reduction/r0011011.c new file mode 100644 index 0000000000000000000000000000000000000000..e3e49a964b9b91f02d535443f015cfcb7025ea43 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011011.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r0011011.c.hs b/rtree-c/test/expected/add/reduction/r0011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0011100.c b/rtree-c/test/expected/add/reduction/r0011100.c new file mode 100644 index 0000000000000000000000000000000000000000..d1d7f5b52e090585f57e09f219a0f837e11d48c4 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011100.c @@ -0,0 +1,15 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) + +int add(int a) +{ +} +int main() +{ + return add(10); +} diff --git a/rtree-c/test/expected/add/reduction/r0011100.c.hs b/rtree-c/test/expected/add/reduction/r0011100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011100.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0011101.c b/rtree-c/test/expected/add/reduction/r0011101.c new file mode 100644 index 0000000000000000000000000000000000000000..0b2fe43026a8cd32ffa039435859070d302062d5 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011101.c @@ -0,0 +1,15 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) + +int add(int a) +{ +} +int main() +{ + return add(0); +} diff --git a/rtree-c/test/expected/add/reduction/r0011101.c.hs b/rtree-c/test/expected/add/reduction/r0011101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011101.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0011110.c b/rtree-c/test/expected/add/reduction/r0011110.c new file mode 100644 index 0000000000000000000000000000000000000000..426782c9fbac42b14b83988b8f78dc6ee73546dd --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011110.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r0011110.c.hs b/rtree-c/test/expected/add/reduction/r0011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0011111.c b/rtree-c/test/expected/add/reduction/r0011111.c new file mode 100644 index 0000000000000000000000000000000000000000..714ce13fb91f313e8b75bc9693354136042118a4 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011111.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 2) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r0011111.c.hs b/rtree-c/test/expected/add/reduction/r0011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r0011111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r01000.c b/rtree-c/test/expected/add/reduction/r010000.c similarity index 84% rename from rtree-c/test/expected/add/reduction/r01000.c rename to rtree-c/test/expected/add/reduction/r010000.c index 2463667a7f167fb59c501ab2f5a7d9549cf4b3f0..262510cca1a813305f3bc521991cd9774ba9a5d0 100644 --- a/rtree-c/test/expected/add/reduction/r01000.c +++ b/rtree-c/test/expected/add/reduction/r010000.c @@ -1,6 +1,7 @@ // 0 remove function add at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 0 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r010000.c.hs b/rtree-c/test/expected/add/reduction/r010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r01001.c b/rtree-c/test/expected/add/reduction/r010001.c similarity index 84% rename from rtree-c/test/expected/add/reduction/r01001.c rename to rtree-c/test/expected/add/reduction/r010001.c index 5a914f298ad85aa4880fced1f920d8b76ec8b692..4024a9e99d18f085e09baf590ef75156530bbe56 100644 --- a/rtree-c/test/expected/add/reduction/r01001.c +++ b/rtree-c/test/expected/add/reduction/r010001.c @@ -1,6 +1,7 @@ // 0 remove function add at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) // 1 do without param at ("test/cases/small/add.c": line 6) diff --git a/rtree-c/test/expected/add/reduction/r010001.c.hs b/rtree-c/test/expected/add/reduction/r010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0101.c b/rtree-c/test/expected/add/reduction/r010010.c similarity index 68% rename from rtree-c/test/expected/add/reduction/r0101.c rename to rtree-c/test/expected/add/reduction/r010010.c index 49eb1c955117b27972783ab9a4c8a9544545db1d..a378b9852b0e6d664ce0227d2b6cccacccb763b0 100644 --- a/rtree-c/test/expected/add/reduction/r0101.c +++ b/rtree-c/test/expected/add/reduction/r010010.c @@ -1,7 +1,9 @@ // 0 remove function add at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add(int b) { diff --git a/rtree-c/test/expected/add/reduction/r010010.c.hs b/rtree-c/test/expected/add/reduction/r010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r010011.c b/rtree-c/test/expected/add/reduction/r010011.c new file mode 100644 index 0000000000000000000000000000000000000000..9823c417090c9fa1c5876577a2736e8569d1678f --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010011.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int b) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r010011.c.hs b/rtree-c/test/expected/add/reduction/r010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r010100.c b/rtree-c/test/expected/add/reduction/r010100.c new file mode 100644 index 0000000000000000000000000000000000000000..73156b446a58733dd313d9b8068d115f6e423110 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010100.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 0 do without param at ("test/cases/small/add.c": line 6) + +int add(int b) +{ +} +int main() +{ + return add(23); +} diff --git a/rtree-c/test/expected/add/reduction/r010100.c.hs b/rtree-c/test/expected/add/reduction/r010100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010100.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r010101.c b/rtree-c/test/expected/add/reduction/r010101.c new file mode 100644 index 0000000000000000000000000000000000000000..346f93b85e00f15d9d7b1878c9f806c5638e724a --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010101.c @@ -0,0 +1,14 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) +// 1 do without param at ("test/cases/small/add.c": line 6) + +int add(int b) +{ +} +int main() +{ + return add(0); +} diff --git a/rtree-c/test/expected/add/reduction/r010101.c.hs b/rtree-c/test/expected/add/reduction/r010101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010101.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r010110.c b/rtree-c/test/expected/add/reduction/r010110.c new file mode 100644 index 0000000000000000000000000000000000000000..4fa29265d5524c5906ed285e250fcc02d4353c40 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010110.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int b) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r010110.c.hs b/rtree-c/test/expected/add/reduction/r010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r010111.c b/rtree-c/test/expected/add/reduction/r010111.c new file mode 100644 index 0000000000000000000000000000000000000000..526c58d671ace3777d9a4bef1c1f7a85ceccbc04 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010111.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add(int b) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r010111.c.hs b/rtree-c/test/expected/add/reduction/r010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r010111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0110.c b/rtree-c/test/expected/add/reduction/r01100.c similarity index 82% rename from rtree-c/test/expected/add/reduction/r0110.c rename to rtree-c/test/expected/add/reduction/r01100.c index cff4021ec931f785fd83b053778d3a69446137d0..795f55b6932a775bb5b10e5d348323d437a7aa2c 100644 --- a/rtree-c/test/expected/add/reduction/r0110.c +++ b/rtree-c/test/expected/add/reduction/r01100.c @@ -1,6 +1,7 @@ // 0 remove function add at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 0 remove return statement at ("test/cases/small/add.c": line 6) int add() diff --git a/rtree-c/test/expected/add/reduction/r01100.c.hs b/rtree-c/test/expected/add/reduction/r01100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r01100.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r0111.c b/rtree-c/test/expected/add/reduction/r011010.c similarity index 68% rename from rtree-c/test/expected/add/reduction/r0111.c rename to rtree-c/test/expected/add/reduction/r011010.c index d62e6f234627b5293919c5ca176ad2ba5d5bf8c3..dd3af1ce7b7871c019e7c4842dbc05c6f21e61f2 100644 --- a/rtree-c/test/expected/add/reduction/r0111.c +++ b/rtree-c/test/expected/add/reduction/r011010.c @@ -1,7 +1,9 @@ // 0 remove function add at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) // 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int add() { diff --git a/rtree-c/test/expected/add/reduction/r011010.c.hs b/rtree-c/test/expected/add/reduction/r011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r011011.c b/rtree-c/test/expected/add/reduction/r011011.c new file mode 100644 index 0000000000000000000000000000000000000000..ee11fbd5227c399d254dcdec2bc0121134fa779c --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011011.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 0 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r011011.c.hs b/rtree-c/test/expected/add/reduction/r011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r01110.c b/rtree-c/test/expected/add/reduction/r01110.c new file mode 100644 index 0000000000000000000000000000000000000000..3afb2191e56c550bcfb0ddf4b3cf042ff1754401 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r01110.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 0 remove return statement at ("test/cases/small/add.c": line 6) + +int add() +{ +} +int main() +{ + return add(); +} diff --git a/rtree-c/test/expected/add/reduction/r01110.c.hs b/rtree-c/test/expected/add/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r01110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r011110.c b/rtree-c/test/expected/add/reduction/r011110.c new file mode 100644 index 0000000000000000000000000000000000000000..c9ba2ccd733380eb283c4e1a2d0519b7d9ff5d38 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011110.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) + +int add() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r011110.c.hs b/rtree-c/test/expected/add/reduction/r011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r011111.c b/rtree-c/test/expected/add/reduction/r011111.c new file mode 100644 index 0000000000000000000000000000000000000000..5de8f092bd4d835d703e487300d8543f37893739 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011111.c @@ -0,0 +1,13 @@ +// 0 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove parameter at ("test/cases/small/add.c": line 1) +// 1 remove empty compound at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int add() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r011111.c.hs b/rtree-c/test/expected/add/reduction/r011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r011111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r1000.c.hs b/rtree-c/test/expected/add/reduction/r1000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r1000.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r1001.c.hs b/rtree-c/test/expected/add/reduction/r1001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r1001.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r1010.c.hs b/rtree-c/test/expected/add/reduction/r1010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r1010.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r1011.c.hs b/rtree-c/test/expected/add/reduction/r1011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r1011.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r11.c b/rtree-c/test/expected/add/reduction/r110.c similarity index 69% rename from rtree-c/test/expected/add/reduction/r11.c rename to rtree-c/test/expected/add/reduction/r110.c index 8ef1eede7261c9d92b33a2c23b78c174328ef62b..ab0b03b4991375ba1443f9e6b9c86a1ad45c8ca1 100644 --- a/rtree-c/test/expected/add/reduction/r11.c +++ b/rtree-c/test/expected/add/reduction/r110.c @@ -1,5 +1,6 @@ // 1 remove function add at ("test/cases/small/add.c": line 1) // 1 remove return statement at ("test/cases/small/add.c": line 6) +// 0 remove empty compound at ("test/cases/small/add.c": line 5) int main() { diff --git a/rtree-c/test/expected/add/reduction/r110.c.hs b/rtree-c/test/expected/add/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r110.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/add/reduction/r111.c b/rtree-c/test/expected/add/reduction/r111.c new file mode 100644 index 0000000000000000000000000000000000000000..ae5dc163c442d09d1a23bcc827743f2bc0f086d1 --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r111.c @@ -0,0 +1,7 @@ +// 1 remove function add at ("test/cases/small/add.c": line 1) +// 1 remove return statement at ("test/cases/small/add.c": line 6) +// 1 remove empty compound at ("test/cases/small/add.c": line 5) + +int main() +{ +} diff --git a/rtree-c/test/expected/add/reduction/r111.c.hs b/rtree-c/test/expected/add/reduction/r111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..2535b051bfdbfc9739ceaee80b545d54452e440b --- /dev/null +++ b/rtree-c/test/expected/add/reduction/r111.c.hs @@ -0,0 +1,88 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "add" 1651297 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "b" 98 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CVar + ( Ident "b" 98 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "add" 1651297 () ) () + ) + [ CConst + ( CIntConst 10 () ) + , CConst + ( CIntConst 23 () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/clang-22382/extract.c b/rtree-c/test/expected/clang-22382/extract.c index 8651efe64ad6e289295c37a13a1d47be399570cf..f85e2394d3fe4f864f1a1f3dd8a56a3ca114acf9 100644 --- a/rtree-c/test/expected/clang-22382/extract.c +++ b/rtree-c/test/expected/clang-22382/extract.c @@ -1412,6 +1412,8 @@ static struct S0 func_59(uint32_t p_60, g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; safe_unary_minus_func_int8_t_s(0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL)); + { + } safe_sub_func_int8_t_s_s(0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; @@ -1498,6 +1500,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1532,6 +1536,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; safe_mul_func_int8_t_s_s(g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/p0.path b/rtree-c/test/expected/clang-22382/reduction/p0.path index ca29af7f88edf36c169d18f444b072c86b68ef2c..4389dd3fa511d2e752f09af53ac9e267dce9ac87 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p0.path +++ b/rtree-c/test/expected/clang-22382/reduction/p0.path @@ -2285,6 +2285,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4329,6 +4330,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4613,6 +4616,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4708,6 +4713,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p1.path b/rtree-c/test/expected/clang-22382/reduction/p1.path index 05d92e853efa1f8abd4603c3e7fd717a69a5b376..088913aee43df0fd66802660acfd8eaa79377410 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p1.path +++ b/rtree-c/test/expected/clang-22382/reduction/p1.path @@ -2314,6 +2314,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4358,6 +4359,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4642,6 +4645,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4737,6 +4742,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p2.path b/rtree-c/test/expected/clang-22382/reduction/p2.path index 129643e7449981d9bc9890bb2b57ffe675bb48ba..1c15867694dfab95c8c5acc8dda593c65afdb268 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p2.path +++ b/rtree-c/test/expected/clang-22382/reduction/p2.path @@ -2343,6 +2343,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4387,6 +4388,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4671,6 +4674,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4766,6 +4771,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p3.path b/rtree-c/test/expected/clang-22382/reduction/p3.path index acf96e75fc231d5d8bb3f16df02e08a372f80c55..9260fcd9c2ca6bc3e4a7bd2f78d440ee3493aca3 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p3.path +++ b/rtree-c/test/expected/clang-22382/reduction/p3.path @@ -2343,6 +2343,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4387,6 +4388,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4671,6 +4674,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4766,6 +4771,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p4.path b/rtree-c/test/expected/clang-22382/reduction/p4.path index cde75b7652ea451e31d07905f0b275a81f472293..03c4e8df3c875e5deadeb80a034b19d101181b8e 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p4.path +++ b/rtree-c/test/expected/clang-22382/reduction/p4.path @@ -2264,6 +2264,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4308,6 +4309,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4592,6 +4595,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4687,6 +4692,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p5.path b/rtree-c/test/expected/clang-22382/reduction/p5.path index 7d0b9492be619c17c9d129fcecd3842e86eb383e..7d445311f46b402838e80072978bb0b2a28cb5f8 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p5.path +++ b/rtree-c/test/expected/clang-22382/reduction/p5.path @@ -2033,6 +2033,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -4077,6 +4078,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -4361,6 +4364,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -4456,6 +4461,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p6.path b/rtree-c/test/expected/clang-22382/reduction/p6.path index 7598a7bbcd27c2c87bda1f11b2d1106ea9d7d881..c5835a4c1ab3f90ea68bcb2df6f5ee023697c6d9 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p6.path +++ b/rtree-c/test/expected/clang-22382/reduction/p6.path @@ -1540,6 +1540,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -3584,6 +3585,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -3868,6 +3871,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -3963,6 +3968,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2474) * reduce to left at ("test/cases/large/clang-22382.c": line 2474) * reduce to right at ("test/cases/large/clang-22382.c": line 2474) diff --git a/rtree-c/test/expected/clang-22382/reduction/p7.path b/rtree-c/test/expected/clang-22382/reduction/p7.path index 2ac1db76b77259fbc5c119861674f15d47a16e87..992be92c8a94cc5f2075a958bf08251878b0e323 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p7.path +++ b/rtree-c/test/expected/clang-22382/reduction/p7.path @@ -399,6 +399,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 1295) * reduce to operant at ("test/cases/large/clang-22382.c": line 1295) * do without param at ("test/cases/large/clang-22382.c": line 1295) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1300) +* expand compound statment at ("test/cases/large/clang-22382.c": line 1300) * remove expr statement at ("test/cases/large/clang-22382.c": line 1304) * reduce to left at ("test/cases/large/clang-22382.c": line 1304) * reduce to right at ("test/cases/large/clang-22382.c": line 1304) @@ -580,6 +582,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1435) * reduce to left at ("test/cases/large/clang-22382.c": line 1435) * reduce to right at ("test/cases/large/clang-22382.c": line 1435) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1436) * remove check at ("test/cases/large/clang-22382.c": line 1435) * remove iterator at ("test/cases/large/clang-22382.c": line 1435) * reduce to operant at ("test/cases/large/clang-22382.c": line 1435) @@ -704,6 +707,7 @@ * remove initializer at ("test/cases/large/clang-22382.c": line 1570) * reduce to left at ("test/cases/large/clang-22382.c": line 1570) * reduce to right at ("test/cases/large/clang-22382.c": line 1570) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1571) * remove check at ("test/cases/large/clang-22382.c": line 1570) * remove iterator at ("test/cases/large/clang-22382.c": line 1570) * reduce to operant at ("test/cases/large/clang-22382.c": line 1570) @@ -1667,6 +1671,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 1905) * do without param at ("test/cases/large/clang-22382.c": line 1905) * do without param at ("test/cases/large/clang-22382.c": line 1905) +* remove empty compound at ("test/cases/large/clang-22382.c": line 1906) +* expand compound statment at ("test/cases/large/clang-22382.c": line 1906) * remove expr statement at ("test/cases/large/clang-22382.c": line 1910) * do without param at ("test/cases/large/clang-22382.c": line 1910) * do without param at ("test/cases/large/clang-22382.c": line 1910) @@ -2077,6 +2083,8 @@ * replace by zero at ("test/cases/large/clang-22382.c": line 2189) * do without param at ("test/cases/large/clang-22382.c": line 2189) * expand compound statment at ("test/cases/large/clang-22382.c": line 2165) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2194) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2194) * inline variable l_1437 at ("test/cases/large/clang-22382.c": line 2204) * remove return statement at ("test/cases/large/clang-22382.c": line 2205) * expand compound statment at ("test/cases/large/clang-22382.c": line 2203) @@ -2118,6 +2126,8 @@ * remove expr statement at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) * do without param at ("test/cases/large/clang-22382.c": line 2238) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2245) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2245) * remove expr statement at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) * do without param at ("test/cases/large/clang-22382.c": line 2255) @@ -2359,6 +2369,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) * do without param at ("test/cases/large/clang-22382.c": line 2381) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2388) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2388) * remove expr statement at ("test/cases/large/clang-22382.c": line 2394) * do without param at ("test/cases/large/clang-22382.c": line 2394) * replace by zero at ("test/cases/large/clang-22382.c": line 2394) @@ -2449,6 +2461,8 @@ * reduce to left at ("test/cases/large/clang-22382.c": line 2456) * reduce to right at ("test/cases/large/clang-22382.c": line 2456) * do without param at ("test/cases/large/clang-22382.c": line 2456) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2463) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2463) * remove expr statement at ("test/cases/large/clang-22382.c": line 2475) * do without param at ("test/cases/large/clang-22382.c": line 2475) * do without param at ("test/cases/large/clang-22382.c": line 2475) @@ -2508,6 +2522,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2526) * do without param at ("test/cases/large/clang-22382.c": line 2526) * do without param at ("test/cases/large/clang-22382.c": line 2526) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2529) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2529) * expand compound statment at ("test/cases/large/clang-22382.c": line 2502) * remove expr statement at ("test/cases/large/clang-22382.c": line 2536) * remove expr statement at ("test/cases/large/clang-22382.c": line 2539) @@ -2606,6 +2622,8 @@ * do without param at ("test/cases/large/clang-22382.c": line 2647) * do without param at ("test/cases/large/clang-22382.c": line 2647) * replace by zero at ("test/cases/large/clang-22382.c": line 2647) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2651) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2651) * remove expr statement at ("test/cases/large/clang-22382.c": line 2655) * do without param at ("test/cases/large/clang-22382.c": line 2655) * do without param at ("test/cases/large/clang-22382.c": line 2655) @@ -2791,6 +2809,9 @@ * remove expr statement at ("test/cases/large/clang-22382.c": line 2825) * do without param at ("test/cases/large/clang-22382.c": line 2825) * do without param at ("test/cases/large/clang-22382.c": line 2825) +* remove empty compound at ("test/cases/large/clang-22382.c": line 2831) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2831) +* expand compound statment at ("test/cases/large/clang-22382.c": line 2828) * remove expr statement at ("test/cases/large/clang-22382.c": line 2837) * do without param at ("test/cases/large/clang-22382.c": line 2837) * do without param at ("test/cases/large/clang-22382.c": line 2837) diff --git a/rtree-c/test/expected/clang-22382/reduction/p9.path b/rtree-c/test/expected/clang-22382/reduction/p9.path index f6ceb31962d3b43e24112e08a2145a9e3220cb1a..08dd519f4b09beb39a3226dbfcba26ce3382f89e 100644 --- a/rtree-c/test/expected/clang-22382/reduction/p9.path +++ b/rtree-c/test/expected/clang-22382/reduction/p9.path @@ -259,37 +259,45 @@ 1 remove condition at ("test/cases/large/clang-22382.c": line 2898) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2898) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2898) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2896) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2907) 1 remove condition at ("test/cases/large/clang-22382.c": line 2908) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2908) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2908) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2906) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2912) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2915) 1 remove condition at ("test/cases/large/clang-22382.c": line 2916) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2916) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2916) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2914) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2918) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2925) 1 remove condition at ("test/cases/large/clang-22382.c": line 2926) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2926) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2926) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2924) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2934) 1 remove condition at ("test/cases/large/clang-22382.c": line 2935) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2935) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2935) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2933) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2940) 1 remove condition at ("test/cases/large/clang-22382.c": line 2941) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2941) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2941) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2939) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2945) 1 remove condition at ("test/cases/large/clang-22382.c": line 2946) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2946) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2946) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2944) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2948) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2951) 1 remove condition at ("test/cases/large/clang-22382.c": line 2952) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2952) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2952) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2950) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2954) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2955) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2958) @@ -299,6 +307,7 @@ 1 remove condition at ("test/cases/large/clang-22382.c": line 2962) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2962) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2962) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2957) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2964) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2965) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2966) @@ -306,10 +315,12 @@ 1 remove condition at ("test/cases/large/clang-22382.c": line 2972) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2972) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2972) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2970) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2981) 1 remove condition at ("test/cases/large/clang-22382.c": line 2982) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2982) 1 expand compound statment at ("test/cases/large/clang-22382.c": line 2982) +1 remove empty compound at ("test/cases/large/clang-22382.c": line 2980) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2986) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2987) 1 remove expr statement at ("test/cases/large/clang-22382.c": line 2988) diff --git a/rtree-c/test/expected/clang-22382/reduction/x0.c b/rtree-c/test/expected/clang-22382/reduction/x0.c index db30d61b0418b878e78847518da6c11ecfedb1aa..a8c33957a04cd15376f9d9b9f9b19779bd1641f3 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x0.c +++ b/rtree-c/test/expected/clang-22382/reduction/x0.c @@ -1407,6 +1407,8 @@ static struct S0 func_59(uint32_t p_60, g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; safe_unary_minus_func_int8_t_s(0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL)); + { + } safe_sub_func_int8_t_s_s(0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; @@ -1493,6 +1495,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1527,6 +1531,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; safe_mul_func_int8_t_s_s(g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x1.c b/rtree-c/test/expected/clang-22382/reduction/x1.c index 736d9f89bbad134c6b6ecba0cc6fa1044a09ce64..446acff9da1c54b00f55f2e63259950d4af68091 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x1.c +++ b/rtree-c/test/expected/clang-22382/reduction/x1.c @@ -1406,6 +1406,8 @@ static struct S0 func_59(uint32_t p_60, g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; safe_unary_minus_func_int8_t_s(0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL)); + { + } safe_sub_func_int8_t_s_s(0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; @@ -1492,6 +1494,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1526,6 +1530,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; safe_mul_func_int8_t_s_s(g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x2.c b/rtree-c/test/expected/clang-22382/reduction/x2.c index b2534d42ce17c68c9b122b51aacec0214b050a46..3a4eef79e88aa0aecdee35c7aa115fce451b15ea 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x2.c +++ b/rtree-c/test/expected/clang-22382/reduction/x2.c @@ -1404,6 +1404,8 @@ static struct S0 func_59(uint32_t p_60, g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; safe_unary_minus_func_int8_t_s(0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL)); + { + } safe_sub_func_int8_t_s_s(0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; @@ -1490,6 +1492,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1524,6 +1528,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; safe_mul_func_int8_t_s_s(g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x3.c b/rtree-c/test/expected/clang-22382/reduction/x3.c index c318b9a09159bf0a9789460b08d057e92d0a928b..9e2d896d12327dbfeeba1174983fd0f29fe305c1 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x3.c +++ b/rtree-c/test/expected/clang-22382/reduction/x3.c @@ -1401,6 +1401,8 @@ static struct S0 func_59(uint32_t p_60, g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; safe_unary_minus_func_int8_t_s(0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL)); + { + } safe_sub_func_int8_t_s_s(0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; @@ -1487,6 +1489,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1521,6 +1525,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; safe_mul_func_int8_t_s_s(g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x4.c b/rtree-c/test/expected/clang-22382/reduction/x4.c index ee2a945a054bd4a29e3339fc81a3543859caf64b..1d8b66a673ba9b3475668256a0a3ef7ed4ddd987 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x4.c +++ b/rtree-c/test/expected/clang-22382/reduction/x4.c @@ -1331,6 +1331,8 @@ static struct S0 func_59(uint32_t p_60, int i, j; g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; 0L < safe_add_func_int16_t_s_s(g_35.f3, 0x16abL); + { + } (0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; safe_lshift_func_uint16_t_u_s(safe_mul_func_uint8_t_u_u(1uL, @@ -1411,6 +1413,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_rshift_func_int8_t_s_u(safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1442,6 +1446,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; (g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x5.c b/rtree-c/test/expected/clang-22382/reduction/x5.c index 4449a82c25885b51e41930618828fc118ca1f937..e26b3aadac928772d288a148879c01f77dbf72d9 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x5.c +++ b/rtree-c/test/expected/clang-22382/reduction/x5.c @@ -1194,6 +1194,8 @@ static struct S0 func_59(uint32_t p_60, int i, j; g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; 0L < (g_35.f3, 0x16abL); + { + } (0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; safe_lshift_func_uint16_t_u_s(safe_mul_func_uint8_t_u_u(1uL, @@ -1262,6 +1264,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) safe_add_func_uint8_t_u_u(g_85, 1); (safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1292,6 +1296,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; (g_388.f3, 7uL); safe_mod_func_int64_t_s_s(252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x6.c b/rtree-c/test/expected/clang-22382/reduction/x6.c index 884f4a997ebb24e61acea421057389108199cf27..7faf9622084d1c05e99bb623c4f65ea8524296ac 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x6.c +++ b/rtree-c/test/expected/clang-22382/reduction/x6.c @@ -978,6 +978,8 @@ static struct S0 func_59(uint32_t p_60, int i, j; g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; 0L < (g_35.f3, 0x16abL); + { + } (0x5cL, safe_rshift_func_uint16_t_u_u(0xd7eeL, 14)); g_158 -= 1; safe_lshift_func_uint16_t_u_s((1uL, g_420[2][1] < p_64.f3), @@ -1039,6 +1041,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) (g_85, 1); (safe_lshift_func_uint16_t_u_u(g_158, 12) == 0x70b449b74578e65aLL, 2); + { + } safe_rshift_func_uint16_t_u_u(g_755[5] < (0x70e0L != safe_sub_func_uint32_t_u_u((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); @@ -1068,6 +1072,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) l_168 += 1; g_86 |= 0xffL; (252uL ^ g_251, 0x54eab2ce98b21cf8LL); + { + } g_251 += 1; (g_388.f3, 7uL); (252uL ^ g_251, 0x54eab2ce98b21cf8LL); diff --git a/rtree-c/test/expected/clang-22382/reduction/x7.c b/rtree-c/test/expected/clang-22382/reduction/x7.c index 2db04dd35d011706f81de184907f7f94c37de857..01f55224dcbf4c44d1f8110b4510e7b619ac9e28 100644 --- a/rtree-c/test/expected/clang-22382/reduction/x7.c +++ b/rtree-c/test/expected/clang-22382/reduction/x7.c @@ -123,6 +123,8 @@ static int64_t func_1() g_506 &= 0x387e3cdf10492640LL; } (-4L, 5); + { + } g_1103 += 1; (-4L, 5); ((0x6d2bL, 12), g_1032[4]); @@ -465,6 +467,8 @@ static uint16_t func_51(int16_t p_52, } (g_420[2][1], 255uL); ("index = [%d][%d][%d]\n", i, j, k); + { + } (65527uL, 0xbd2ee514L); for (; 0L < 6;) { @@ -608,6 +612,8 @@ static uint16_t func_51(int16_t p_52, (~(l_1240.f0 < l_1362) && g_390, g_421[3][7][1]), l_1427), 4294967295uL), p_54); } + { + } { uint32_t l_1437 = 0xa9a030fbL; return l_1437; @@ -638,6 +644,8 @@ static struct S0 func_59(uint32_t p_60, int i, j; g_1109 ^= 0xface4f9578fc59a3LL <= 0x61490d3a8ca6555aLL; 0L < 0x16abL; + { + } (0x5cL, (0xd7eeL, 14)); ((1uL, g_420[2][1] < p_64.f3), p_64.f0); (0L, 1); @@ -692,6 +700,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) ("index = [%d][%d][%d]\n", i, j, k); (0x89ab98cfL, 1); ((0L, 12) == 0x70b449b74578e65aLL, 2); + { + } (g_755[5] < (0x70e0L != ((g_755[7], g_1109), 1uL) || g_1145[0].f2), 2); (1uL, 0x5e27L); for (j = 0; j < 3; j++) @@ -716,6 +726,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) (0xbeL, 253uL); l_168 += 1; (252uL ^ 0xb89a725eL, 0x54eab2ce98b21cf8LL); + { + } (g_388.f3, 7uL); (252uL ^ 0xb89a725eL, 0x54eab2ce98b21cf8LL); (l_168, 7); @@ -734,6 +746,8 @@ static int32_t func_66(uint16_t p_67, struct S0 p_68) (0xbad58878L < 7uL != g_594, 4); (0x720fL == 0x14d4L, 0x1e7b790c5a96d6b6LL); ("index = [%d][%d][%d]\n", i, j, k); + { + } } func_78(0); (9uL, ((p_68.f2 <= 0x35c9L, l_230), 65534uL)); @@ -772,6 +786,8 @@ static int32_t func_71(uint8_t p_72, uint32_t p_73, uint32_t p_74) g_506 <= (g_388.f1 < g_420[1][5]); g_388.f1 -= 1; ((0x6d2bL, 12), g_1032[4]); + { + } (0x1823L, 11); ((g_388.f0, 0xd95d3b69L), (g_1032[4], 0x46L)); (9uL, 1); @@ -830,6 +846,10 @@ static uint8_t func_78(uint32_t p_79) (func_78(0), 0x89ab98cfL); (g_1756[0][0][6] || 0x96ae7fbL, 13); (0xbd2ee514L, 0); + { + { + } + } (8L, 0x9ed3L); { ((g_388.f0, 0xd95d3b69L), (g_1032[4], 0x46L)); diff --git a/rtree-c/test/expected/clang-23353/reduction/p0.path b/rtree-c/test/expected/clang-23353/reduction/p0.path index 31e2f16e8eb5d4532bf86f3fbdf6ed426eb95c36..c43f922598bc42a27dca669cd95501a69d189a49 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p0.path +++ b/rtree-c/test/expected/clang-23353/reduction/p0.path @@ -495,6 +495,7 @@ * remove parameter at ("test/cases/large/clang-23353.c": line 1250) * remove parameter at ("test/cases/large/clang-23353.c": line 1250) * remove variable func_49 at ("test/cases/large/clang-23353.c": line 1250) +* remove empty compound at ("test/cases/large/clang-23353.c": line 13) * remove static at ("test/cases/large/clang-23353.c": line 14) * remove expr statement at ("test/cases/large/clang-23353.c": line 22) * do without param at ("test/cases/large/clang-23353.c": line 22) diff --git a/rtree-c/test/expected/clang-23353/reduction/p1.path b/rtree-c/test/expected/clang-23353/reduction/p1.path index ea4ad26b2d22510824a6f25c03eeb27d7584d0c6..7582f88e12e19d13c518d488d3aa5565b9ad90e8 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p1.path +++ b/rtree-c/test/expected/clang-23353/reduction/p1.path @@ -495,6 +495,7 @@ * remove parameter at ("test/cases/large/clang-23353.c": line 1250) * remove parameter at ("test/cases/large/clang-23353.c": line 1250) * remove variable func_49 at ("test/cases/large/clang-23353.c": line 1250) +* remove empty compound at ("test/cases/large/clang-23353.c": line 13) * remove static at ("test/cases/large/clang-23353.c": line 14) * remove expr statement at ("test/cases/large/clang-23353.c": line 22) * do without param at ("test/cases/large/clang-23353.c": line 22) diff --git a/rtree-c/test/expected/clang-23353/reduction/p10.path b/rtree-c/test/expected/clang-23353/reduction/p10.path index 0c270bae40b695f5b036351a61468683d1088b6c..54cbdd1903f4e7265618d3c80b2371e21c57951a 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p10.path +++ b/rtree-c/test/expected/clang-23353/reduction/p10.path @@ -363,6 +363,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3812) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3813) 1 remove condition at ("test/cases/large/clang-23353.c": line 3814) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3815) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3814) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3821) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3822) @@ -382,6 +383,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3836) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3837) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3838) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3840) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3839) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3846) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3847) @@ -395,6 +397,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3855) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3856) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3857) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3859) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3858) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3865) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3866) @@ -415,6 +418,7 @@ 1 inline variable l_1353 at ("test/cases/large/clang-23353.c": line 3882) 1 inline variable l_1364 at ("test/cases/large/clang-23353.c": line 3883) 1 inline variable l_1403 at ("test/cases/large/clang-23353.c": line 3884) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3875) 1 remove check at ("test/cases/large/clang-23353.c": line 3874) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3871) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3890) @@ -439,6 +443,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3909) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3910) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3911) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3913) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3912) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3919) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3920) @@ -446,6 +451,8 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3922) 1 remove condition at ("test/cases/large/clang-23353.c": line 3923) 1 inline variable l_817 at ("test/cases/large/clang-23353.c": line 3927) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3926) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3924) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3923) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3934) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3935) @@ -471,6 +478,8 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3955) 1 remove variable l_124 at ("test/cases/large/clang-23353.c": line 3960) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3963) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3959) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3957) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3956) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3970) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3971) @@ -497,6 +506,8 @@ 1 remove variable l_4144 at ("test/cases/large/clang-23353.c": line 3992) 1 remove declaration at ("test/cases/large/clang-23353.c": line 3992) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3995) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3989) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3987) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3986) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 4000) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 4001) diff --git a/rtree-c/test/expected/clang-23353/reduction/p7.path b/rtree-c/test/expected/clang-23353/reduction/p7.path index 3c918e0fc5a3a6d5c94f3e49600a9276d50e8ffb..6d90f6f8e09d7e6b243844fe1a58861eabf1b5b2 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p7.path +++ b/rtree-c/test/expected/clang-23353/reduction/p7.path @@ -5440,6 +5440,7 @@ * reduce to operant at ("test/cases/large/clang-23353.c": line 3138) * remove expression at ("test/cases/large/clang-23353.c": line 3138) * remove return statement at ("test/cases/large/clang-23353.c": line 3144) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3139) * remove expr statement at ("test/cases/large/clang-23353.c": line 3148) * do without param at ("test/cases/large/clang-23353.c": line 3148) * do without param at ("test/cases/large/clang-23353.c": line 3148) @@ -7151,6 +7152,7 @@ * do without param at ("test/cases/large/clang-23353.c": line 3813) * remove condition at ("test/cases/large/clang-23353.c": line 3814) * reduce to operant at ("test/cases/large/clang-23353.c": line 3814) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3815) * remove expr statement at ("test/cases/large/clang-23353.c": line 3821) * do without param at ("test/cases/large/clang-23353.c": line 3821) * do without param at ("test/cases/large/clang-23353.c": line 3821) @@ -7437,6 +7439,7 @@ * reduce to operant at ("test/cases/large/clang-23353.c": line 3912) * reduce to operant at ("test/cases/large/clang-23353.c": line 3912) * reduce to operant at ("test/cases/large/clang-23353.c": line 3912) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3913) * remove expr statement at ("test/cases/large/clang-23353.c": line 3919) * do without param at ("test/cases/large/clang-23353.c": line 3919) * do without param at ("test/cases/large/clang-23353.c": line 3919) diff --git a/rtree-c/test/expected/clang-23353/reduction/p8.path b/rtree-c/test/expected/clang-23353/reduction/p8.path index dde2df6d553ed0ef15bf8b66d6c6c4cd89b5e6fb..3f904092b78e3730356018bde111cb4d91a3d128 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p8.path +++ b/rtree-c/test/expected/clang-23353/reduction/p8.path @@ -3566,6 +3566,8 @@ * reduce to operant at ("test/cases/large/clang-23353.c": line 2728) * remove iterator at ("test/cases/large/clang-23353.c": line 2728) * reduce to operant at ("test/cases/large/clang-23353.c": line 2728) +* remove empty compound at ("test/cases/large/clang-23353.c": line 2741) +* expand compound statment at ("test/cases/large/clang-23353.c": line 2741) * remove expr statement at ("test/cases/large/clang-23353.c": line 2746) * reduce to left at ("test/cases/large/clang-23353.c": line 2746) * reduce to right at ("test/cases/large/clang-23353.c": line 2746) @@ -4833,6 +4835,7 @@ * reduce to operant at ("test/cases/large/clang-23353.c": line 3138) * remove expression at ("test/cases/large/clang-23353.c": line 3138) * remove return statement at ("test/cases/large/clang-23353.c": line 3144) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3139) * remove expr statement at ("test/cases/large/clang-23353.c": line 3148) * do without param at ("test/cases/large/clang-23353.c": line 3148) * do without param at ("test/cases/large/clang-23353.c": line 3148) @@ -6500,6 +6503,7 @@ * do without param at ("test/cases/large/clang-23353.c": line 3813) * remove condition at ("test/cases/large/clang-23353.c": line 3814) * reduce to operant at ("test/cases/large/clang-23353.c": line 3814) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3815) * remove expr statement at ("test/cases/large/clang-23353.c": line 3821) * do without param at ("test/cases/large/clang-23353.c": line 3821) * do without param at ("test/cases/large/clang-23353.c": line 3821) @@ -6595,6 +6599,7 @@ * remove expr statement at ("test/cases/large/clang-23353.c": line 3857) * do without param at ("test/cases/large/clang-23353.c": line 3857) * do without param at ("test/cases/large/clang-23353.c": line 3857) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3859) * expand compound statment at ("test/cases/large/clang-23353.c": line 3858) * remove expr statement at ("test/cases/large/clang-23353.c": line 3865) * do without param at ("test/cases/large/clang-23353.c": line 3865) @@ -6703,6 +6708,7 @@ * do without param at ("test/cases/large/clang-23353.c": line 3911) * do without param at ("test/cases/large/clang-23353.c": line 3911) * do without param at ("test/cases/large/clang-23353.c": line 3911) +* remove empty compound at ("test/cases/large/clang-23353.c": line 3913) * expand compound statment at ("test/cases/large/clang-23353.c": line 3912) * remove expr statement at ("test/cases/large/clang-23353.c": line 3919) * do without param at ("test/cases/large/clang-23353.c": line 3919) diff --git a/rtree-c/test/expected/clang-23353/reduction/p9.path b/rtree-c/test/expected/clang-23353/reduction/p9.path index a52eaae1e33303e754e35dd1073380e1579a2857..6ea0d5877166e160860ba544dc804f92ec991b4c 100644 --- a/rtree-c/test/expected/clang-23353/reduction/p9.path +++ b/rtree-c/test/expected/clang-23353/reduction/p9.path @@ -363,6 +363,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3812) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3813) 1 remove condition at ("test/cases/large/clang-23353.c": line 3814) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3815) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3814) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3821) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3822) @@ -382,6 +383,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3836) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3837) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3838) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3840) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3839) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3846) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3847) @@ -395,6 +397,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3855) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3856) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3857) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3859) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3858) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3865) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3866) @@ -415,6 +418,7 @@ 1 inline variable l_1353 at ("test/cases/large/clang-23353.c": line 3882) 1 inline variable l_1364 at ("test/cases/large/clang-23353.c": line 3883) 1 inline variable l_1403 at ("test/cases/large/clang-23353.c": line 3884) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3875) 1 remove check at ("test/cases/large/clang-23353.c": line 3874) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3871) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3890) @@ -439,6 +443,7 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3909) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3910) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3911) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3913) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3912) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3919) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3920) @@ -446,6 +451,8 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3922) 1 remove condition at ("test/cases/large/clang-23353.c": line 3923) 1 inline variable l_817 at ("test/cases/large/clang-23353.c": line 3927) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3926) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3924) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3923) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3934) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3935) @@ -471,6 +478,8 @@ 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3955) 1 remove variable l_124 at ("test/cases/large/clang-23353.c": line 3960) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3963) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3959) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3957) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3956) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3970) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3971) @@ -497,18 +506,45 @@ 1 remove variable l_4144 at ("test/cases/large/clang-23353.c": line 3992) 1 remove declaration at ("test/cases/large/clang-23353.c": line 3992) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 3995) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3989) +1 remove empty compound at ("test/cases/large/clang-23353.c": line 3987) 1 expand compound statment at ("test/cases/large/clang-23353.c": line 3986) 1 remove expr statement at ("test/cases/large/clang-23353.c": line 4000) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4001) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4002) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4003) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4004) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4005) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4006) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4007) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4008) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4009) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4010) -1 remove expr statement at ("test/cases/large/clang-23353.c": line 4011) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4001) +* do without param at ("test/cases/large/clang-23353.c": line 4001) +* do without param at ("test/cases/large/clang-23353.c": line 4001) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4002) +* do without param at ("test/cases/large/clang-23353.c": line 4002) +* do without param at ("test/cases/large/clang-23353.c": line 4002) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4003) +* do without param at ("test/cases/large/clang-23353.c": line 4003) +* do without param at ("test/cases/large/clang-23353.c": line 4003) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4004) +* do without param at ("test/cases/large/clang-23353.c": line 4004) +* do without param at ("test/cases/large/clang-23353.c": line 4004) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4005) +* do without param at ("test/cases/large/clang-23353.c": line 4005) +* do without param at ("test/cases/large/clang-23353.c": line 4005) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4006) +* do without param at ("test/cases/large/clang-23353.c": line 4006) +* do without param at ("test/cases/large/clang-23353.c": line 4006) +* do without param at ("test/cases/large/clang-23353.c": line 4006) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4007) +* do without param at ("test/cases/large/clang-23353.c": line 4007) +* do without param at ("test/cases/large/clang-23353.c": line 4007) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4008) +* do without param at ("test/cases/large/clang-23353.c": line 4008) +* do without param at ("test/cases/large/clang-23353.c": line 4008) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4009) +* do without param at ("test/cases/large/clang-23353.c": line 4009) +* do without param at ("test/cases/large/clang-23353.c": line 4009) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4010) +* do without param at ("test/cases/large/clang-23353.c": line 4010) +* do without param at ("test/cases/large/clang-23353.c": line 4010) +* remove expr statement at ("test/cases/large/clang-23353.c": line 4011) +* do without param at ("test/cases/large/clang-23353.c": line 4011) +* reduce to left at ("test/cases/large/clang-23353.c": line 4011) +* reduce to right at ("test/cases/large/clang-23353.c": line 4011) +* do without param at ("test/cases/large/clang-23353.c": line 4011) * remove return statement at ("test/cases/large/clang-23353.c": line 4012) diff --git a/rtree-c/test/expected/clang-23353/reduction/x7.c b/rtree-c/test/expected/clang-23353/reduction/x7.c index 0137a4f5f0b9c3bcf58ec3ed8750efb25fa939e2..046ee09361b542167cd8dd25b3d73a94fc267619 100644 --- a/rtree-c/test/expected/clang-23353/reduction/x7.c +++ b/rtree-c/test/expected/clang-23353/reduction/x7.c @@ -2560,7 +2560,9 @@ int main(void) (g_803.f2, "g_803.f2", print_hash_value); (g_803.f3, "g_803.f3", print_hash_value); (g_803.f4, "g_803.f4", print_hash_value); - 0xe07f0936a74b4fbfLL < -2270085556831825985; + if (0xe07f0936a74b4fbfLL < -2270085556831825985) + { + } (g_803.f5, "g_803.f5", print_hash_value); (g_804.f0, "g_804.f0", print_hash_value); (g_804.f1, "g_804.f1", print_hash_value); @@ -2642,7 +2644,9 @@ int main(void) (g_2213.f2, "g_2213.f2", print_hash_value); (g_2213.f3, "g_2213.f3", print_hash_value); (g_2243, "g_2243", print_hash_value); - g_2976 != 0 && *g_2976 != 0 && * (*g_2976) != 0 && * (*g_2976) < 0; + if (g_2976 != 0 && *g_2976 != 0 && * (*g_2976) != 0 && * (*g_2976) < 0) + { + } (g_2309, "g_2309", print_hash_value); (g_2321.f0, "g_2321.f0", print_hash_value); (g_2321.f1, "g_2321.f1", print_hash_value); diff --git a/rtree-c/test/expected/clang-23353/reduction/x8.c b/rtree-c/test/expected/clang-23353/reduction/x8.c index 3af314877a8a8fdff6acdc86e2254008643452a6..80c2650776adb10a15feafc50309995c73278a92 100644 --- a/rtree-c/test/expected/clang-23353/reduction/x8.c +++ b/rtree-c/test/expected/clang-23353/reduction/x8.c @@ -1486,6 +1486,8 @@ static const uint8_t func_43(uint64_t p_44, int32_t l_1364 = 1L; int32_t l_1403 = 1L; } + { + } l_1440 = l_1439; 0 ? (void) 0 : ("l_1440 == &g_804", "t.c", 1622, __PRETTY_FUNCTION__); for (; 0xccL < 42;) @@ -2495,7 +2497,9 @@ int main(void) ("g_803.f2", print_hash_value); ("g_803.f3", print_hash_value); ("g_803.f4", print_hash_value); - 0xe07f0936a74b4fbfLL < -2270085556831825985; + if (0xe07f0936a74b4fbfLL < -2270085556831825985) + { + } ("g_803.f5", print_hash_value); ("g_804.f0", print_hash_value); ("g_804.f1", print_hash_value); diff --git a/rtree-c/test/expected/clang-23353/reduction/x9.c b/rtree-c/test/expected/clang-23353/reduction/x9.c index ac1e2770c60bc5248e4e3d7d15bf3435e11cc310..ae3fc4b021858a4d881aee90cb773f80bb630ad4 100644 --- a/rtree-c/test/expected/clang-23353/reduction/x9.c +++ b/rtree-c/test/expected/clang-23353/reduction/x9.c @@ -13,5 +13,16 @@ int main(void) { } ; + ("g_4141.f5", 0); + ("g_4181.f0", 0); + ("g_4181.f1", 0); + ("g_4181.f2", 0); + ("g_4181.f3", 0); + (65532uL, "g_4582", 0); + ("g_4585.f0", 0); + ("g_4585.f1", 0); + ("g_4585.f2", 0); + ("g_4585.f3", 0); + (0xffffffffuL ^ 0xffffffffuL, 0); return 0; } diff --git a/rtree-c/test/expected/clang-26760/reduction/p9.path b/rtree-c/test/expected/clang-26760/reduction/p9.path index f6f6c287ce57afa2f7bb7d425a00aeded3303f52..5d2a8e764938aa26a68dc60f4cc778adf27876ae 100644 --- a/rtree-c/test/expected/clang-26760/reduction/p9.path +++ b/rtree-c/test/expected/clang-26760/reduction/p9.path @@ -261,12 +261,14 @@ 1 remove condition at ("test/cases/large/clang-26760.c": line 13379) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13380) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13379) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13377) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13382) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13383) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13386) 1 remove condition at ("test/cases/large/clang-26760.c": line 13387) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13388) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13387) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13385) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13390) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13391) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13392) @@ -276,6 +278,7 @@ 1 remove condition at ("test/cases/large/clang-26760.c": line 13398) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13399) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13398) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13396) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13401) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13402) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13403) @@ -284,27 +287,33 @@ 1 remove condition at ("test/cases/large/clang-26760.c": line 13408) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13409) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13408) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13406) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13417) 1 remove condition at ("test/cases/large/clang-26760.c": line 13420) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13421) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13420) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13416) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13429) 1 remove condition at ("test/cases/large/clang-26760.c": line 13430) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13431) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13430) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13428) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13440) 1 remove condition at ("test/cases/large/clang-26760.c": line 13443) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13444) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13443) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13439) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13450) 1 remove condition at ("test/cases/large/clang-26760.c": line 13451) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13452) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13451) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13449) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13454) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13459) 1 remove condition at ("test/cases/large/clang-26760.c": line 13460) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13461) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13460) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13458) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13464) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13465) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13466) @@ -315,6 +324,7 @@ 1 remove condition at ("test/cases/large/clang-26760.c": line 13479) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13480) 1 expand compound statment at ("test/cases/large/clang-26760.c": line 13479) +1 remove empty compound at ("test/cases/large/clang-26760.c": line 13475) 1 remove expr statement at ("test/cases/large/clang-26760.c": line 13484) 1 remove return statement at ("test/cases/large/clang-26760.c": line 13485) diff --git a/rtree-c/test/expected/constant/reduction/r00000.c.hs b/rtree-c/test/expected/constant/reduction/r00000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r00000.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r00001.c.hs b/rtree-c/test/expected/constant/reduction/r00001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r00001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r0001.c.hs b/rtree-c/test/expected/constant/reduction/r0001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r001.c.hs b/rtree-c/test/expected/constant/reduction/r001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r01000.c.hs b/rtree-c/test/expected/constant/reduction/r01000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r01000.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r01001.c.hs b/rtree-c/test/expected/constant/reduction/r01001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r01001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r0101.c.hs b/rtree-c/test/expected/constant/reduction/r0101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0101.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r011.c b/rtree-c/test/expected/constant/reduction/r0110.c similarity index 76% rename from rtree-c/test/expected/constant/reduction/r011.c rename to rtree-c/test/expected/constant/reduction/r0110.c index 0e611cbda4fbbac74c0e1e7b37b8a441e136a19a..10a730e701df528826fc6be77417a8d5e1d90b0c 100644 --- a/rtree-c/test/expected/constant/reduction/r011.c +++ b/rtree-c/test/expected/constant/reduction/r0110.c @@ -1,6 +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 return statement at ("test/cases/small/constant.c": line 5) +// 0 remove empty compound at ("test/cases/small/constant.c": line 3) int x = 10; int main() diff --git a/rtree-c/test/expected/constant/reduction/r0110.c.hs b/rtree-c/test/expected/constant/reduction/r0110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0110.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r0111.c b/rtree-c/test/expected/constant/reduction/r0111.c new file mode 100644 index 0000000000000000000000000000000000000000..aaef7305fff70ca8d01af919fb4fd6f233d10963 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0111.c @@ -0,0 +1,9 @@ +// 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 return statement at ("test/cases/small/constant.c": line 5) +// 1 remove empty compound at ("test/cases/small/constant.c": line 3) + +int x = 10; +int main() +{ +} diff --git a/rtree-c/test/expected/constant/reduction/r0111.c.hs b/rtree-c/test/expected/constant/reduction/r0111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r0111.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r10000.c.hs b/rtree-c/test/expected/constant/reduction/r10000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r10000.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r10001.c.hs b/rtree-c/test/expected/constant/reduction/r10001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r10001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r1001.c.hs b/rtree-c/test/expected/constant/reduction/r1001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r101.c.hs b/rtree-c/test/expected/constant/reduction/r101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r101.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r11000.c.hs b/rtree-c/test/expected/constant/reduction/r11000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r11000.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r11001.c.hs b/rtree-c/test/expected/constant/reduction/r11001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r11001.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r1101.c.hs b/rtree-c/test/expected/constant/reduction/r1101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1101.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r111.c b/rtree-c/test/expected/constant/reduction/r1110.c similarity index 75% rename from rtree-c/test/expected/constant/reduction/r111.c rename to rtree-c/test/expected/constant/reduction/r1110.c index 72a38fd5dc224cca8becc480799344a8d0e082f8..c03bf1d58821873a29dd4c84e6d0ef88e91793c9 100644 --- a/rtree-c/test/expected/constant/reduction/r111.c +++ b/rtree-c/test/expected/constant/reduction/r1110.c @@ -1,6 +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 return statement at ("test/cases/small/constant.c": line 5) +// 0 remove empty compound at ("test/cases/small/constant.c": line 3) int main() { diff --git a/rtree-c/test/expected/constant/reduction/r1110.c.hs b/rtree-c/test/expected/constant/reduction/r1110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1110.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/constant/reduction/r1111.c b/rtree-c/test/expected/constant/reduction/r1111.c new file mode 100644 index 0000000000000000000000000000000000000000..ab1f2de8134ecd0d771e0d593305039588565e71 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1111.c @@ -0,0 +1,8 @@ +// 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 return statement at ("test/cases/small/constant.c": line 5) +// 1 remove empty compound at ("test/cases/small/constant.c": line 3) + +int main() +{ +} diff --git a/rtree-c/test/expected/constant/reduction/r1111.c.hs b/rtree-c/test/expected/constant/reduction/r1111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f3fe70dd10b560c8dadc8b9078734e089e0daf99 --- /dev/null +++ b/rtree-c/test/expected/constant/reduction/r1111.c.hs @@ -0,0 +1,72 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 10 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 25 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CBinary CAddOp + ( CVar + ( Ident "x" 120 () ) () + ) + ( CVar + ( Ident "y" 121 () ) () + ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r0000.c.hs b/rtree-c/test/expected/declaration/reduction/r0000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r0000.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r0001.c.hs b/rtree-c/test/expected/declaration/reduction/r0001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r0001.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r0010.c.hs b/rtree-c/test/expected/declaration/reduction/r0010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r0010.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r0011.c.hs b/rtree-c/test/expected/declaration/reduction/r0011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r0011.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r01.c b/rtree-c/test/expected/declaration/reduction/r010.c similarity index 72% rename from rtree-c/test/expected/declaration/reduction/r01.c rename to rtree-c/test/expected/declaration/reduction/r010.c index 4caade54fc8cf028bf2effe107a66af1f94c3393..554e67ccfb10464dd2efd7c1b590f50a915c3d31 100644 --- a/rtree-c/test/expected/declaration/reduction/r01.c +++ b/rtree-c/test/expected/declaration/reduction/r010.c @@ -1,5 +1,6 @@ // 0 remove variable printf at ("test/cases/small/declaration.c": line 1) // 1 remove expr statement at ("test/cases/small/declaration.c": line 4) +// 0 remove empty compound at ("test/cases/small/declaration.c": line 3) int printf(const char *, ...); int main() diff --git a/rtree-c/test/expected/declaration/reduction/r010.c.hs b/rtree-c/test/expected/declaration/reduction/r010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r010.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r011.c b/rtree-c/test/expected/declaration/reduction/r011.c new file mode 100644 index 0000000000000000000000000000000000000000..abfa6eaf008d7b35e4a8b3482bcd12bc56c1a8ed --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r011.c @@ -0,0 +1,8 @@ +// 0 remove variable printf at ("test/cases/small/declaration.c": line 1) +// 1 remove expr statement at ("test/cases/small/declaration.c": line 4) +// 1 remove empty compound at ("test/cases/small/declaration.c": line 3) + +int printf(const char *, ...); +int main() +{ +} diff --git a/rtree-c/test/expected/declaration/reduction/r011.c.hs b/rtree-c/test/expected/declaration/reduction/r011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r011.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r100.c.hs b/rtree-c/test/expected/declaration/reduction/r100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r100.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r101.c.hs b/rtree-c/test/expected/declaration/reduction/r101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r101.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r11.c b/rtree-c/test/expected/declaration/reduction/r110.c similarity index 69% rename from rtree-c/test/expected/declaration/reduction/r11.c rename to rtree-c/test/expected/declaration/reduction/r110.c index 6a962b22af3fddc776a4c9ea9dbe6de0bc5a0d3d..a2a5cd3685471edf0ed9e2f0b935d3d9e5764e97 100644 --- a/rtree-c/test/expected/declaration/reduction/r11.c +++ b/rtree-c/test/expected/declaration/reduction/r110.c @@ -1,5 +1,6 @@ // 1 remove variable printf at ("test/cases/small/declaration.c": line 1) // 1 remove expr statement at ("test/cases/small/declaration.c": line 4) +// 0 remove empty compound at ("test/cases/small/declaration.c": line 3) int main() { diff --git a/rtree-c/test/expected/declaration/reduction/r110.c.hs b/rtree-c/test/expected/declaration/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r110.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/declaration/reduction/r111.c b/rtree-c/test/expected/declaration/reduction/r111.c new file mode 100644 index 0000000000000000000000000000000000000000..975d1c6de3b254ea58bc516bf9d99e783a4baa6a --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r111.c @@ -0,0 +1,7 @@ +// 1 remove variable printf at ("test/cases/small/declaration.c": line 1) +// 1 remove expr statement at ("test/cases/small/declaration.c": line 4) +// 1 remove empty compound at ("test/cases/small/declaration.c": line 3) + +int main() +{ +} diff --git a/rtree-c/test/expected/declaration/reduction/r111.c.hs b/rtree-c/test/expected/declaration/reduction/r111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..9608e860484368f1bea841bf8eb03ec049b4ccea --- /dev/null +++ b/rtree-c/test/expected/declaration/reduction/r111.c.hs @@ -0,0 +1,61 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "printf" 232434916 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeQual + ( CConstQual () ) + , CTypeSpec + ( CCharType () ) + ] + [ CDeclarationItem + ( CDeclr Nothing + [ CPtrDeclr [] () ] Nothing [] () + ) Nothing Nothing + ] () + ] True + ) [] () + ] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "printf" 232434916 () ) () + ) + [ CConst + ( CStrConst "Hello, World!" () ) + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r000.c.hs b/rtree-c/test/expected/definition/reduction/r000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r000.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r001.c b/rtree-c/test/expected/definition/reduction/r0010.c similarity index 78% rename from rtree-c/test/expected/definition/reduction/r001.c rename to rtree-c/test/expected/definition/reduction/r0010.c index d774277e08e5fcdcd3dfef482de57bf50441be07..18561daef21b3ecedb0b3f4eb3126835e8493d61 100644 --- a/rtree-c/test/expected/definition/reduction/r001.c +++ b/rtree-c/test/expected/definition/reduction/r0010.c @@ -1,6 +1,7 @@ // 0 remove function f at ("test/cases/small/definition.c": line 1) // 0 remove return statement at ("test/cases/small/definition.c": line 2) // 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 0 remove empty compound at ("test/cases/small/definition.c": line 5) int f() { diff --git a/rtree-c/test/expected/definition/reduction/r0010.c.hs b/rtree-c/test/expected/definition/reduction/r0010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0010.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r0011.c b/rtree-c/test/expected/definition/reduction/r0011.c new file mode 100644 index 0000000000000000000000000000000000000000..65af645f7d45eeee5acf4b1e9e5838f3c3bff4f8 --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0011.c @@ -0,0 +1,12 @@ +// 0 remove function f at ("test/cases/small/definition.c": line 1) +// 0 remove return statement at ("test/cases/small/definition.c": line 2) +// 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 1 remove empty compound at ("test/cases/small/definition.c": line 5) + +int f() +{ + return 0; +} +int main() +{ +} diff --git a/rtree-c/test/expected/definition/reduction/r0011.c.hs b/rtree-c/test/expected/definition/reduction/r0011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0011.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r010.c b/rtree-c/test/expected/definition/reduction/r0100.c similarity index 78% rename from rtree-c/test/expected/definition/reduction/r010.c rename to rtree-c/test/expected/definition/reduction/r0100.c index 6ec9fb808204a7d7c2d15a69dbd456847f46acf2..d1b246028dfbe923d91bff63c79883dff8323527 100644 --- a/rtree-c/test/expected/definition/reduction/r010.c +++ b/rtree-c/test/expected/definition/reduction/r0100.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/definition.c": line 1) // 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 0 remove empty compound at ("test/cases/small/definition.c": line 1) // 0 remove return statement at ("test/cases/small/definition.c": line 6) int f() diff --git a/rtree-c/test/expected/definition/reduction/r0100.c.hs b/rtree-c/test/expected/definition/reduction/r0100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0100.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r011.c b/rtree-c/test/expected/definition/reduction/r01010.c similarity index 62% rename from rtree-c/test/expected/definition/reduction/r011.c rename to rtree-c/test/expected/definition/reduction/r01010.c index 5003e4d565b099748639992c99b86f9d433dbdd5..4013d98f28a0a25a1385e3bfbcae2d12438d83b1 100644 --- a/rtree-c/test/expected/definition/reduction/r011.c +++ b/rtree-c/test/expected/definition/reduction/r01010.c @@ -1,6 +1,8 @@ // 0 remove function f at ("test/cases/small/definition.c": line 1) // 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 0 remove empty compound at ("test/cases/small/definition.c": line 1) // 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 0 remove empty compound at ("test/cases/small/definition.c": line 5) int f() { diff --git a/rtree-c/test/expected/definition/reduction/r01010.c.hs b/rtree-c/test/expected/definition/reduction/r01010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01010.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r01011.c b/rtree-c/test/expected/definition/reduction/r01011.c new file mode 100644 index 0000000000000000000000000000000000000000..ed367434faf59f4dbd25cf593d43d734ce355131 --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01011.c @@ -0,0 +1,12 @@ +// 0 remove function f at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 0 remove empty compound at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 1 remove empty compound at ("test/cases/small/definition.c": line 5) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/definition/reduction/r01011.c.hs b/rtree-c/test/expected/definition/reduction/r01011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01011.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r0110.c b/rtree-c/test/expected/definition/reduction/r0110.c new file mode 100644 index 0000000000000000000000000000000000000000..c24e77ec12c21bb4150005e2f770f4d9ea7fadef --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0110.c @@ -0,0 +1,12 @@ +// 0 remove function f at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 1 remove empty compound at ("test/cases/small/definition.c": line 1) +// 0 remove return statement at ("test/cases/small/definition.c": line 6) + +int f() +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/definition/reduction/r0110.c.hs b/rtree-c/test/expected/definition/reduction/r0110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r0110.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r01110.c b/rtree-c/test/expected/definition/reduction/r01110.c new file mode 100644 index 0000000000000000000000000000000000000000..8879ce9f9878f7584330aa03f618bfc0d7a3c78e --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01110.c @@ -0,0 +1,12 @@ +// 0 remove function f at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 1 remove empty compound at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 0 remove empty compound at ("test/cases/small/definition.c": line 5) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/definition/reduction/r01110.c.hs b/rtree-c/test/expected/definition/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01110.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r01111.c b/rtree-c/test/expected/definition/reduction/r01111.c new file mode 100644 index 0000000000000000000000000000000000000000..7455363fc5ddf7bf79d0defa1deefef1611e249d --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01111.c @@ -0,0 +1,12 @@ +// 0 remove function f at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 2) +// 1 remove empty compound at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 1 remove empty compound at ("test/cases/small/definition.c": line 5) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/definition/reduction/r01111.c.hs b/rtree-c/test/expected/definition/reduction/r01111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r01111.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r10.c.hs b/rtree-c/test/expected/definition/reduction/r10.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r10.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r11.c b/rtree-c/test/expected/definition/reduction/r110.c similarity index 68% rename from rtree-c/test/expected/definition/reduction/r11.c rename to rtree-c/test/expected/definition/reduction/r110.c index 1564cc3d81bde5bf4a24afe785f9db27b1d39173..0c5a740f3a195659c85041f75832e4a033cb870e 100644 --- a/rtree-c/test/expected/definition/reduction/r11.c +++ b/rtree-c/test/expected/definition/reduction/r110.c @@ -1,5 +1,6 @@ // 1 remove function f at ("test/cases/small/definition.c": line 1) // 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 0 remove empty compound at ("test/cases/small/definition.c": line 5) int main() { diff --git a/rtree-c/test/expected/definition/reduction/r110.c.hs b/rtree-c/test/expected/definition/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r110.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/definition/reduction/r111.c b/rtree-c/test/expected/definition/reduction/r111.c new file mode 100644 index 0000000000000000000000000000000000000000..50a544594b654bcb58c4a05d157dbf636db855cc --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r111.c @@ -0,0 +1,7 @@ +// 1 remove function f at ("test/cases/small/definition.c": line 1) +// 1 remove return statement at ("test/cases/small/definition.c": line 6) +// 1 remove empty compound at ("test/cases/small/definition.c": line 5) + +int main() +{ +} diff --git a/rtree-c/test/expected/definition/reduction/r111.c.hs b/rtree-c/test/expected/definition/reduction/r111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..adadaee19b87097189750a531bb052d990cf7e0f --- /dev/null +++ b/rtree-c/test/expected/definition/reduction/r111.c.hs @@ -0,0 +1,54 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CConst + ( CIntConst 0 () ) + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) [] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r00000.c b/rtree-c/test/expected/for/reduction/r000000.c similarity index 84% rename from rtree-c/test/expected/for/reduction/r00000.c rename to rtree-c/test/expected/for/reduction/r000000.c index 59d6a66da2164ae41a1daccc167b5e01531bca02..cb0ad0b245b6355aaedff69880c56450e821731b 100644 --- a/rtree-c/test/expected/for/reduction/r00000.c +++ b/rtree-c/test/expected/for/reduction/r000000.c @@ -3,6 +3,7 @@ // 0 remove initializer at ("test/cases/small/for.c": line 4) // 0 reduce to left at ("test/cases/small/for.c": line 4) // 0 reduce to right at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) static int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r000000.c.hs b/rtree-c/test/expected/for/reduction/r000000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000000.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r000001.c b/rtree-c/test/expected/for/reduction/r000001.c new file mode 100644 index 0000000000000000000000000000000000000000..8300117b92351aa366539495ec1e20b744eec5bf --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000001.c @@ -0,0 +1,14 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 0 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 0 reduce to left at ("test/cases/small/for.c": line 4) +// 0 reduce to right at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +static int a = 0; +int main() +{ + for (a = 0;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r000001.c.hs b/rtree-c/test/expected/for/reduction/r000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000001.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r00001.c b/rtree-c/test/expected/for/reduction/r000010.c similarity index 84% rename from rtree-c/test/expected/for/reduction/r00001.c rename to rtree-c/test/expected/for/reduction/r000010.c index 9e8dd579a02177e69df619696062d6156b0f3723..958c7b6415d2fc8fdcd743f3b65f9f38ca043917 100644 --- a/rtree-c/test/expected/for/reduction/r00001.c +++ b/rtree-c/test/expected/for/reduction/r000010.c @@ -3,6 +3,7 @@ // 0 remove initializer at ("test/cases/small/for.c": line 4) // 0 reduce to left at ("test/cases/small/for.c": line 4) // 1 reduce to right at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) static int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r000010.c.hs b/rtree-c/test/expected/for/reduction/r000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000010.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r000011.c b/rtree-c/test/expected/for/reduction/r000011.c new file mode 100644 index 0000000000000000000000000000000000000000..3e1f08b117cc9a14d8dcfbec922193c2ab541abf --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000011.c @@ -0,0 +1,14 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 0 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 0 reduce to left at ("test/cases/small/for.c": line 4) +// 1 reduce to right at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +static int a = 0; +int main() +{ + for (0;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r000011.c.hs b/rtree-c/test/expected/for/reduction/r000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r000011.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r0001.c b/rtree-c/test/expected/for/reduction/r00010.c similarity index 82% rename from rtree-c/test/expected/for/reduction/r0001.c rename to rtree-c/test/expected/for/reduction/r00010.c index d71841f23480656d84eb2746dd30fc1b545ddff5..a58f913c8a98eedceab57d425e6ad694359f2baa 100644 --- a/rtree-c/test/expected/for/reduction/r0001.c +++ b/rtree-c/test/expected/for/reduction/r00010.c @@ -2,6 +2,7 @@ // 0 remove static at ("test/cases/small/for.c": line 1) // 0 remove initializer at ("test/cases/small/for.c": line 4) // 1 reduce to left at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) static int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r00010.c.hs b/rtree-c/test/expected/for/reduction/r00010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r00010.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r00011.c b/rtree-c/test/expected/for/reduction/r00011.c new file mode 100644 index 0000000000000000000000000000000000000000..b988cd7f1ff6d33b3f62cffae8a9ab8e864ce4d8 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r00011.c @@ -0,0 +1,13 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 0 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 1 reduce to left at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +static int a = 0; +int main() +{ + for (a;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r00011.c.hs b/rtree-c/test/expected/for/reduction/r00011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r00011.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r001.c b/rtree-c/test/expected/for/reduction/r0010.c similarity index 78% rename from rtree-c/test/expected/for/reduction/r001.c rename to rtree-c/test/expected/for/reduction/r0010.c index a6df43132e428ec08161f6c501a1b94e982142c0..d8181bf4703c8b5aec110fa2fbb8f8b5f64851a9 100644 --- a/rtree-c/test/expected/for/reduction/r001.c +++ b/rtree-c/test/expected/for/reduction/r0010.c @@ -1,6 +1,7 @@ // 0 inline variable a at ("test/cases/small/for.c": line 1) // 0 remove static at ("test/cases/small/for.c": line 1) // 1 remove initializer at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) static int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r0010.c.hs b/rtree-c/test/expected/for/reduction/r0010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0010.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r0011.c b/rtree-c/test/expected/for/reduction/r0011.c new file mode 100644 index 0000000000000000000000000000000000000000..b96bfe1796097c69c62a0b703768194b2657ef16 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0011.c @@ -0,0 +1,12 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 0 remove static at ("test/cases/small/for.c": line 1) +// 1 remove initializer at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +static int a = 0; +int main() +{ + for (;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r0011.c.hs b/rtree-c/test/expected/for/reduction/r0011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0011.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r01000.c b/rtree-c/test/expected/for/reduction/r010000.c similarity index 84% rename from rtree-c/test/expected/for/reduction/r01000.c rename to rtree-c/test/expected/for/reduction/r010000.c index 900304cd0ca1f0625b06e314f44a3c108de80c19..5fe1c0b2d4263e3edc84bc700583ca5796c797e2 100644 --- a/rtree-c/test/expected/for/reduction/r01000.c +++ b/rtree-c/test/expected/for/reduction/r010000.c @@ -3,6 +3,7 @@ // 0 remove initializer at ("test/cases/small/for.c": line 4) // 0 reduce to left at ("test/cases/small/for.c": line 4) // 0 reduce to right at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r010000.c.hs b/rtree-c/test/expected/for/reduction/r010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010000.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r010001.c b/rtree-c/test/expected/for/reduction/r010001.c new file mode 100644 index 0000000000000000000000000000000000000000..4236d05ee07e7dd6a899107fbf51256feec41be2 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010001.c @@ -0,0 +1,14 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 1 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 0 reduce to left at ("test/cases/small/for.c": line 4) +// 0 reduce to right at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +int a = 0; +int main() +{ + for (a = 0;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r010001.c.hs b/rtree-c/test/expected/for/reduction/r010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010001.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r01001.c b/rtree-c/test/expected/for/reduction/r010010.c similarity index 84% rename from rtree-c/test/expected/for/reduction/r01001.c rename to rtree-c/test/expected/for/reduction/r010010.c index a5ace4aa0d97a4703853f6d1e91833677d254bd8..811a7a69a3d291b50530abd868f1a6e642b676b0 100644 --- a/rtree-c/test/expected/for/reduction/r01001.c +++ b/rtree-c/test/expected/for/reduction/r010010.c @@ -3,6 +3,7 @@ // 0 remove initializer at ("test/cases/small/for.c": line 4) // 0 reduce to left at ("test/cases/small/for.c": line 4) // 1 reduce to right at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r010010.c.hs b/rtree-c/test/expected/for/reduction/r010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010010.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r010011.c b/rtree-c/test/expected/for/reduction/r010011.c new file mode 100644 index 0000000000000000000000000000000000000000..de101b4aa656c7d003570c6d2667b42b12349433 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010011.c @@ -0,0 +1,14 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 1 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 0 reduce to left at ("test/cases/small/for.c": line 4) +// 1 reduce to right at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +int a = 0; +int main() +{ + for (0;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r010011.c.hs b/rtree-c/test/expected/for/reduction/r010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r010011.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r0101.c b/rtree-c/test/expected/for/reduction/r01010.c similarity index 81% rename from rtree-c/test/expected/for/reduction/r0101.c rename to rtree-c/test/expected/for/reduction/r01010.c index a0adfc8959d9c8bf355739c94be31fe6474c5c7a..d0e4bbf5cedf2e92261213bb755cc73317b1a699 100644 --- a/rtree-c/test/expected/for/reduction/r0101.c +++ b/rtree-c/test/expected/for/reduction/r01010.c @@ -2,6 +2,7 @@ // 1 remove static at ("test/cases/small/for.c": line 1) // 0 remove initializer at ("test/cases/small/for.c": line 4) // 1 reduce to left at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r01010.c.hs b/rtree-c/test/expected/for/reduction/r01010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r01010.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r01011.c b/rtree-c/test/expected/for/reduction/r01011.c new file mode 100644 index 0000000000000000000000000000000000000000..af38507c335d9fd6f57d81acd467af1c85ab8bc4 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r01011.c @@ -0,0 +1,13 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 1 remove static at ("test/cases/small/for.c": line 1) +// 0 remove initializer at ("test/cases/small/for.c": line 4) +// 1 reduce to left at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +int a = 0; +int main() +{ + for (a;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r01011.c.hs b/rtree-c/test/expected/for/reduction/r01011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r01011.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r011.c b/rtree-c/test/expected/for/reduction/r0110.c similarity index 78% rename from rtree-c/test/expected/for/reduction/r011.c rename to rtree-c/test/expected/for/reduction/r0110.c index c3b59ac41546be609c286e4b00376b3cdbdc386d..a89475b65a4fee33bd198b6e75dc83fd91244cf3 100644 --- a/rtree-c/test/expected/for/reduction/r011.c +++ b/rtree-c/test/expected/for/reduction/r0110.c @@ -1,6 +1,7 @@ // 0 inline variable a at ("test/cases/small/for.c": line 1) // 1 remove static at ("test/cases/small/for.c": line 1) // 1 remove initializer at ("test/cases/small/for.c": line 4) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) int a = 0; int main() diff --git a/rtree-c/test/expected/for/reduction/r0110.c.hs b/rtree-c/test/expected/for/reduction/r0110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0110.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r0111.c b/rtree-c/test/expected/for/reduction/r0111.c new file mode 100644 index 0000000000000000000000000000000000000000..d936ce0895ca1c81f6fb972b9e4df017567401b5 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0111.c @@ -0,0 +1,12 @@ +// 0 inline variable a at ("test/cases/small/for.c": line 1) +// 1 remove static at ("test/cases/small/for.c": line 1) +// 1 remove initializer at ("test/cases/small/for.c": line 4) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +int a = 0; +int main() +{ + for (;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r0111.c.hs b/rtree-c/test/expected/for/reduction/r0111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r0111.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r1.c b/rtree-c/test/expected/for/reduction/r10.c similarity index 61% rename from rtree-c/test/expected/for/reduction/r1.c rename to rtree-c/test/expected/for/reduction/r10.c index b99962f496215c7cd695aff1178e47373643ec24..8c7a31caf85b194da7847492f57adfc4098afc50 100644 --- a/rtree-c/test/expected/for/reduction/r1.c +++ b/rtree-c/test/expected/for/reduction/r10.c @@ -1,4 +1,5 @@ // 1 inline variable a at ("test/cases/small/for.c": line 1) +// 0 remove empty compound at ("test/cases/small/for.c": line 4) int main() { diff --git a/rtree-c/test/expected/for/reduction/r10.c.hs b/rtree-c/test/expected/for/reduction/r10.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r10.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/for/reduction/r11.c b/rtree-c/test/expected/for/reduction/r11.c new file mode 100644 index 0000000000000000000000000000000000000000..c3507ba9463d58e295a3e8d403af2eec7875fdf0 --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r11.c @@ -0,0 +1,9 @@ +// 1 inline variable a at ("test/cases/small/for.c": line 1) +// 1 remove empty compound at ("test/cases/small/for.c": line 4) + +int main() +{ + for (;;) + { + } +} diff --git a/rtree-c/test/expected/for/reduction/r11.c.hs b/rtree-c/test/expected/for/reduction/r11.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae --- /dev/null +++ b/rtree-c/test/expected/for/reduction/r11.c.hs @@ -0,0 +1,57 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CStatic () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CFor + ( CForInitializing + ( Just + ( CAssign CAssignOp + ( CVar + ( Ident "a" 97 () ) () + ) + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) + ) Nothing Nothing + ( CCompound [] [] () ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00000000.c b/rtree-c/test/expected/functions/reduction/r000000000.c similarity index 89% rename from rtree-c/test/expected/functions/reduction/r00000000.c rename to rtree-c/test/expected/functions/reduction/r000000000.c index 543338b7f486df08742ea471e9f8f9a6579ce229..48db573eac32e4b1a1ade33b0ad19419af506721 100644 --- a/rtree-c/test/expected/functions/reduction/r00000000.c +++ b/rtree-c/test/expected/functions/reduction/r000000000.c @@ -3,6 +3,7 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r000000000.c.hs b/rtree-c/test/expected/functions/reduction/r000000000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000000000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000000001.c b/rtree-c/test/expected/functions/reduction/r000000001.c new file mode 100644 index 0000000000000000000000000000000000000000..df1433b89b460f84d1d474f373a4a8d91eeb91d9 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000000001.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ + return f(g(0)); +} diff --git a/rtree-c/test/expected/functions/reduction/r000000001.c.hs b/rtree-c/test/expected/functions/reduction/r000000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000000001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00000001.c b/rtree-c/test/expected/functions/reduction/r00000001.c index 66abac8bb9c90139702b0e6d01caf5d807753d9c..e8511e789c70c057ba4407c6c98e6a8beeaa4a3e 100644 --- a/rtree-c/test/expected/functions/reduction/r00000001.c +++ b/rtree-c/test/expected/functions/reduction/r00000001.c @@ -3,8 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) -// 0 do without param at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) int f(int a) @@ -16,5 +16,5 @@ int g(int a) } int main() { - return f(g(0)); + return f(0); } diff --git a/rtree-c/test/expected/functions/reduction/r00000001.c.hs b/rtree-c/test/expected/functions/reduction/r00000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000001.c b/rtree-c/test/expected/functions/reduction/r00000010.c similarity index 76% rename from rtree-c/test/expected/functions/reduction/r000001.c rename to rtree-c/test/expected/functions/reduction/r00000010.c index df38e3802fff0bd19fce670f5c8d370008e3f6b2..6ba5aedc8f0bd4ce11c991e00251f8edf9090f24 100644 --- a/rtree-c/test/expected/functions/reduction/r000001.c +++ b/rtree-c/test/expected/functions/reduction/r00000010.c @@ -3,7 +3,9 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r00000010.c.hs b/rtree-c/test/expected/functions/reduction/r00000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00000011.c b/rtree-c/test/expected/functions/reduction/r00000011.c new file mode 100644 index 0000000000000000000000000000000000000000..6414c8710a88022082ddbcc676e94882b94dfe93 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00000011.c.hs b/rtree-c/test/expected/functions/reduction/r00000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000001000.c b/rtree-c/test/expected/functions/reduction/r000001000.c new file mode 100644 index 0000000000000000000000000000000000000000..66c3869660bbd421342438cafcc39ac99fbccaef --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000001000.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ + return f(g(42)); +} diff --git a/rtree-c/test/expected/functions/reduction/r000001000.c.hs b/rtree-c/test/expected/functions/reduction/r000001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000001000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000001001.c b/rtree-c/test/expected/functions/reduction/r000001001.c new file mode 100644 index 0000000000000000000000000000000000000000..0a87c9a0d4d7456a28e9db0ee565005c3190806e --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000001001.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ + return f(g(0)); +} diff --git a/rtree-c/test/expected/functions/reduction/r000001001.c.hs b/rtree-c/test/expected/functions/reduction/r000001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000001001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000001.c b/rtree-c/test/expected/functions/reduction/r00000101.c similarity index 88% rename from rtree-c/test/expected/functions/reduction/r0000001.c rename to rtree-c/test/expected/functions/reduction/r00000101.c index f7b815a815fce8685481e7a710f2e46df4a4c595..da6fa13c7ec01ba9c4d68a332fa04120a7b182fa 100644 --- a/rtree-c/test/expected/functions/reduction/r0000001.c +++ b/rtree-c/test/expected/functions/reduction/r00000101.c @@ -3,6 +3,7 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r00000101.c.hs b/rtree-c/test/expected/functions/reduction/r00000101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00000110.c b/rtree-c/test/expected/functions/reduction/r00000110.c new file mode 100644 index 0000000000000000000000000000000000000000..d0159c299411e5a020703d9e2b1c7b34297c2428 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00000110.c.hs b/rtree-c/test/expected/functions/reduction/r00000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00000111.c b/rtree-c/test/expected/functions/reduction/r00000111.c new file mode 100644 index 0000000000000000000000000000000000000000..fde2f96bfc98e9b5da1e927332fce7a7cf4ab6c4 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00000111.c.hs b/rtree-c/test/expected/functions/reduction/r00000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00000111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00001000.c b/rtree-c/test/expected/functions/reduction/r0000100000.c similarity index 81% rename from rtree-c/test/expected/functions/reduction/r00001000.c rename to rtree-c/test/expected/functions/reduction/r0000100000.c index 6367eecbc4c607d74b30a26fc724aeebeb0b61fc..044cb464b63ba662c8ba3fc8d4f99914518eca48 100644 --- a/rtree-c/test/expected/functions/reduction/r00001000.c +++ b/rtree-c/test/expected/functions/reduction/r0000100000.c @@ -3,6 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r0000100000.c.hs b/rtree-c/test/expected/functions/reduction/r0000100000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000100000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00001001.c b/rtree-c/test/expected/functions/reduction/r0000100001.c similarity index 81% rename from rtree-c/test/expected/functions/reduction/r00001001.c rename to rtree-c/test/expected/functions/reduction/r0000100001.c index d166d3f8ba7b0838f9825eeb6e70b458657b7377..95b3b77c263e968d65ee95b6d2d93484709eec3f 100644 --- a/rtree-c/test/expected/functions/reduction/r00001001.c +++ b/rtree-c/test/expected/functions/reduction/r0000100001.c @@ -3,6 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r0000100001.c.hs b/rtree-c/test/expected/functions/reduction/r0000100001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000100001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000101.c b/rtree-c/test/expected/functions/reduction/r000010001.c similarity index 79% rename from rtree-c/test/expected/functions/reduction/r0000101.c rename to rtree-c/test/expected/functions/reduction/r000010001.c index e9045962fe872a83859f9332e244fc3fbfc64e2c..e8a82a023a7040368154817db6ed556aa4030c6d 100644 --- a/rtree-c/test/expected/functions/reduction/r0000101.c +++ b/rtree-c/test/expected/functions/reduction/r000010001.c @@ -3,6 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r000010001.c.hs b/rtree-c/test/expected/functions/reduction/r000010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011.c b/rtree-c/test/expected/functions/reduction/r000010010.c similarity index 68% rename from rtree-c/test/expected/functions/reduction/r000011.c rename to rtree-c/test/expected/functions/reduction/r000010010.c index f110d87d077704722a1f0c09448bc01fcf114328..7e926cb5bf3acac8a7b9c891d689b73f7d0c2925 100644 --- a/rtree-c/test/expected/functions/reduction/r000011.c +++ b/rtree-c/test/expected/functions/reduction/r000010010.c @@ -3,7 +3,10 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r000010010.c.hs b/rtree-c/test/expected/functions/reduction/r000010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000010011.c b/rtree-c/test/expected/functions/reduction/r000010011.c new file mode 100644 index 0000000000000000000000000000000000000000..aaacd6acf7a19ab921d638c7c3b8e416fc17b7c4 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000010011.c.hs b/rtree-c/test/expected/functions/reduction/r000010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000101000.c b/rtree-c/test/expected/functions/reduction/r0000101000.c new file mode 100644 index 0000000000000000000000000000000000000000..d924cca68c08b4bec3e9f51b9ab821b9cfe2c19e --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000101000.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(42)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000101000.c.hs b/rtree-c/test/expected/functions/reduction/r0000101000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000101000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000101001.c b/rtree-c/test/expected/functions/reduction/r0000101001.c new file mode 100644 index 0000000000000000000000000000000000000000..9b4469d9bfbe39aee8878919500a120b141b062a --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000101001.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(0)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000101001.c.hs b/rtree-c/test/expected/functions/reduction/r0000101001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000101001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000010101.c b/rtree-c/test/expected/functions/reduction/r000010101.c new file mode 100644 index 0000000000000000000000000000000000000000..f63f0f36067425323edb5dbd31ae11e438edab32 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010101.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000010101.c.hs b/rtree-c/test/expected/functions/reduction/r000010101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000010110.c b/rtree-c/test/expected/functions/reduction/r000010110.c new file mode 100644 index 0000000000000000000000000000000000000000..2eca743e74c2249f6428d588622a56309d2b8c97 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000010110.c.hs b/rtree-c/test/expected/functions/reduction/r000010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000010111.c b/rtree-c/test/expected/functions/reduction/r000010111.c new file mode 100644 index 0000000000000000000000000000000000000000..d21e38197084dad2fa0080e765ebf15bec64e860 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000010111.c.hs b/rtree-c/test/expected/functions/reduction/r000010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000010111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000110000.c b/rtree-c/test/expected/functions/reduction/r0000110000.c new file mode 100644 index 0000000000000000000000000000000000000000..fb999ebf04015c2adcbcfc88a5df44ce30ae3449 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000110000.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(42)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000110000.c.hs b/rtree-c/test/expected/functions/reduction/r0000110000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000110000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000110001.c b/rtree-c/test/expected/functions/reduction/r0000110001.c new file mode 100644 index 0000000000000000000000000000000000000000..c8328b8fac6a1c5ae0ac67c855796ef434685c94 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000110001.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(0)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000110001.c.hs b/rtree-c/test/expected/functions/reduction/r0000110001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000110001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011001.c b/rtree-c/test/expected/functions/reduction/r000011001.c new file mode 100644 index 0000000000000000000000000000000000000000..ebe2ee0d741b7dca48e46164b01d7cabb15d9bf1 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011001.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000011001.c.hs b/rtree-c/test/expected/functions/reduction/r000011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011010.c b/rtree-c/test/expected/functions/reduction/r000011010.c new file mode 100644 index 0000000000000000000000000000000000000000..56ae3facfd677564593b3bb7e50d51f352f94602 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011010.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000011010.c.hs b/rtree-c/test/expected/functions/reduction/r000011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011011.c b/rtree-c/test/expected/functions/reduction/r000011011.c new file mode 100644 index 0000000000000000000000000000000000000000..3fe58564b1b7127f907ff278338dd458afd6d4dd --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000011011.c.hs b/rtree-c/test/expected/functions/reduction/r000011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000111000.c b/rtree-c/test/expected/functions/reduction/r0000111000.c new file mode 100644 index 0000000000000000000000000000000000000000..06f58d0bdc93a85c450c4c339137658727eceae2 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000111000.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(42)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000111000.c.hs b/rtree-c/test/expected/functions/reduction/r0000111000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000111000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0000111001.c b/rtree-c/test/expected/functions/reduction/r0000111001.c new file mode 100644 index 0000000000000000000000000000000000000000..2ebf0ce6d0129a109e531fc9fb5889b0ebea4fe2 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000111001.c @@ -0,0 +1,21 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(g(0)); +} diff --git a/rtree-c/test/expected/functions/reduction/r0000111001.c.hs b/rtree-c/test/expected/functions/reduction/r0000111001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0000111001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011101.c b/rtree-c/test/expected/functions/reduction/r000011101.c new file mode 100644 index 0000000000000000000000000000000000000000..cd954834c21f7c6c11bc89a7eaa7a2a6ba0e16e8 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011101.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000011101.c.hs b/rtree-c/test/expected/functions/reduction/r000011101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011110.c b/rtree-c/test/expected/functions/reduction/r000011110.c new file mode 100644 index 0000000000000000000000000000000000000000..4481f1c21562483d7f12286784c85c3bb614a8cb --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000011110.c.hs b/rtree-c/test/expected/functions/reduction/r000011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000011111.c b/rtree-c/test/expected/functions/reduction/r000011111.c new file mode 100644 index 0000000000000000000000000000000000000000..3fb1ad9a7e463c636ed99a528ee1cd2fd724496f --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000011111.c.hs b/rtree-c/test/expected/functions/reduction/r000011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000011111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0001000.c b/rtree-c/test/expected/functions/reduction/r00010000.c similarity index 88% rename from rtree-c/test/expected/functions/reduction/r0001000.c rename to rtree-c/test/expected/functions/reduction/r00010000.c index 9f79ff2bd38b6d0460237fbb5fae087b5003bf63..126a8d17a683e3cc13425503f9cabdafbdc97919 100644 --- a/rtree-c/test/expected/functions/reduction/r0001000.c +++ b/rtree-c/test/expected/functions/reduction/r00010000.c @@ -3,6 +3,7 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r00010000.c.hs b/rtree-c/test/expected/functions/reduction/r00010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0001001.c b/rtree-c/test/expected/functions/reduction/r00010001.c similarity index 88% rename from rtree-c/test/expected/functions/reduction/r0001001.c rename to rtree-c/test/expected/functions/reduction/r00010001.c index 707a84449530fc42f04ec25cc950b358af61addf..fc0970d42e8a811b73e96548dd673535c3e17a81 100644 --- a/rtree-c/test/expected/functions/reduction/r0001001.c +++ b/rtree-c/test/expected/functions/reduction/r00010001.c @@ -3,6 +3,7 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r00010001.c.hs b/rtree-c/test/expected/functions/reduction/r00010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000101.c b/rtree-c/test/expected/functions/reduction/r00010010.c similarity index 76% rename from rtree-c/test/expected/functions/reduction/r000101.c rename to rtree-c/test/expected/functions/reduction/r00010010.c index f84ccceeca551a844b006ed7da634eb50e96066b..e3f27b3d24f85e3e9fd70a9e6d1858cf37080987 100644 --- a/rtree-c/test/expected/functions/reduction/r000101.c +++ b/rtree-c/test/expected/functions/reduction/r00010010.c @@ -3,7 +3,9 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r00010010.c.hs b/rtree-c/test/expected/functions/reduction/r00010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00010011.c b/rtree-c/test/expected/functions/reduction/r00010011.c new file mode 100644 index 0000000000000000000000000000000000000000..44533ba35f4f3253506decb188d7878a6e1921f4 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00010011.c.hs b/rtree-c/test/expected/functions/reduction/r00010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00010100.c b/rtree-c/test/expected/functions/reduction/r00010100.c new file mode 100644 index 0000000000000000000000000000000000000000..ba46fdcd11db3ac8b9fd4ade37ebd81d12dffe74 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010100.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ + a; +} +int g() +{ +} +int main() +{ + return f(g()); +} diff --git a/rtree-c/test/expected/functions/reduction/r00010100.c.hs b/rtree-c/test/expected/functions/reduction/r00010100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00010101.c b/rtree-c/test/expected/functions/reduction/r00010101.c new file mode 100644 index 0000000000000000000000000000000000000000..6c4744a10d2901441dda6b729aad1af1d340fa12 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010101.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ + a; +} +int g() +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r00010101.c.hs b/rtree-c/test/expected/functions/reduction/r00010101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00010110.c b/rtree-c/test/expected/functions/reduction/r00010110.c new file mode 100644 index 0000000000000000000000000000000000000000..ca1b3c1ba47d924a55b723fab7db0a2d4077290a --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00010110.c.hs b/rtree-c/test/expected/functions/reduction/r00010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00010111.c b/rtree-c/test/expected/functions/reduction/r00010111.c new file mode 100644 index 0000000000000000000000000000000000000000..49ed8c8bffbd7f9dae4d3fefcf25151aa204a5e7 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r00010111.c.hs b/rtree-c/test/expected/functions/reduction/r00010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00010111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0001100.c b/rtree-c/test/expected/functions/reduction/r000110000.c similarity index 79% rename from rtree-c/test/expected/functions/reduction/r0001100.c rename to rtree-c/test/expected/functions/reduction/r000110000.c index 77f59404530918e8de4cd4a65c51c4d9fb64e943..b365e37046eebe2fe1a0176ad2f6e96d74213bf9 100644 --- a/rtree-c/test/expected/functions/reduction/r0001100.c +++ b/rtree-c/test/expected/functions/reduction/r000110000.c @@ -3,6 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r000110000.c.hs b/rtree-c/test/expected/functions/reduction/r000110000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0001101.c b/rtree-c/test/expected/functions/reduction/r000110001.c similarity index 79% rename from rtree-c/test/expected/functions/reduction/r0001101.c rename to rtree-c/test/expected/functions/reduction/r000110001.c index 796824d1ebcbd515185d3a71387903b056fb773c..4bd0d7021de2bdce3ec40063161872bfd72e9445 100644 --- a/rtree-c/test/expected/functions/reduction/r0001101.c +++ b/rtree-c/test/expected/functions/reduction/r000110001.c @@ -3,6 +3,8 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r000110001.c.hs b/rtree-c/test/expected/functions/reduction/r000110001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111.c b/rtree-c/test/expected/functions/reduction/r000110010.c similarity index 68% rename from rtree-c/test/expected/functions/reduction/r000111.c rename to rtree-c/test/expected/functions/reduction/r000110010.c index b5e02bd6d09ce73db3be38234c05408fde491ea9..7b2540bffb65515301db1ab12ba2469e420e8bf5 100644 --- a/rtree-c/test/expected/functions/reduction/r000111.c +++ b/rtree-c/test/expected/functions/reduction/r000110010.c @@ -3,7 +3,10 @@ // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r000110010.c.hs b/rtree-c/test/expected/functions/reduction/r000110010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000110011.c b/rtree-c/test/expected/functions/reduction/r000110011.c new file mode 100644 index 0000000000000000000000000000000000000000..8aca3ea4cf1aacfbb09db1419ee9be372d3333af --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000110011.c.hs b/rtree-c/test/expected/functions/reduction/r000110011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000110100.c b/rtree-c/test/expected/functions/reduction/r000110100.c new file mode 100644 index 0000000000000000000000000000000000000000..6835182d28d863b59725baa72b41b67a2ee558d8 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110100.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(g()); +} diff --git a/rtree-c/test/expected/functions/reduction/r000110100.c.hs b/rtree-c/test/expected/functions/reduction/r000110100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000110101.c b/rtree-c/test/expected/functions/reduction/r000110101.c new file mode 100644 index 0000000000000000000000000000000000000000..384c0d2c517a071933e626fed43b2668c21ccd51 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110101.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000110101.c.hs b/rtree-c/test/expected/functions/reduction/r000110101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000110110.c b/rtree-c/test/expected/functions/reduction/r000110110.c new file mode 100644 index 0000000000000000000000000000000000000000..b417ad1f2aad474417a8ccfa7a9253d48ade527d --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000110110.c.hs b/rtree-c/test/expected/functions/reduction/r000110110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000110111.c b/rtree-c/test/expected/functions/reduction/r000110111.c new file mode 100644 index 0000000000000000000000000000000000000000..e8152a5b27ddc4c7ef2e332e6807319893020f95 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000110111.c.hs b/rtree-c/test/expected/functions/reduction/r000110111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000110111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111000.c b/rtree-c/test/expected/functions/reduction/r000111000.c new file mode 100644 index 0000000000000000000000000000000000000000..8bd0be2faee0a96dcced36c89e9cb868601c9a1d --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111000.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(g()); +} diff --git a/rtree-c/test/expected/functions/reduction/r000111000.c.hs b/rtree-c/test/expected/functions/reduction/r000111000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111001.c b/rtree-c/test/expected/functions/reduction/r000111001.c new file mode 100644 index 0000000000000000000000000000000000000000..034bad1d428346f3af62570583d535bdd166137a --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111001.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000111001.c.hs b/rtree-c/test/expected/functions/reduction/r000111001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111010.c b/rtree-c/test/expected/functions/reduction/r000111010.c new file mode 100644 index 0000000000000000000000000000000000000000..8aff078dd6303b30dbbae1da76f6842590940f10 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111010.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000111010.c.hs b/rtree-c/test/expected/functions/reduction/r000111010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111011.c b/rtree-c/test/expected/functions/reduction/r000111011.c new file mode 100644 index 0000000000000000000000000000000000000000..dc0f73f0b2fa563b193d2bda24121a6f33c6f055 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111011.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000111011.c.hs b/rtree-c/test/expected/functions/reduction/r000111011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111100.c b/rtree-c/test/expected/functions/reduction/r000111100.c new file mode 100644 index 0000000000000000000000000000000000000000..786a7006ef6726bf0101c9880d20e11d2985ff03 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111100.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(g()); +} diff --git a/rtree-c/test/expected/functions/reduction/r000111100.c.hs b/rtree-c/test/expected/functions/reduction/r000111100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111101.c b/rtree-c/test/expected/functions/reduction/r000111101.c new file mode 100644 index 0000000000000000000000000000000000000000..3d92a46b6c6b414419bd193edc1a1e11d691201b --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111101.c @@ -0,0 +1,20 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r000111101.c.hs b/rtree-c/test/expected/functions/reduction/r000111101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111110.c b/rtree-c/test/expected/functions/reduction/r000111110.c new file mode 100644 index 0000000000000000000000000000000000000000..706ec04f60b0a5fcdc1c298b2d50f2db9b163329 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111110.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000111110.c.hs b/rtree-c/test/expected/functions/reduction/r000111110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r000111111.c b/rtree-c/test/expected/functions/reduction/r000111111.c new file mode 100644 index 0000000000000000000000000000000000000000..09dff474c5e7534c19dbbfccf1573683da56773d --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111111.c @@ -0,0 +1,19 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r000111111.c.hs b/rtree-c/test/expected/functions/reduction/r000111111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r000111111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0010000.c.hs b/rtree-c/test/expected/functions/reduction/r0010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0010000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0010001.c.hs b/rtree-c/test/expected/functions/reduction/r0010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0010001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r001001.c.hs b/rtree-c/test/expected/functions/reduction/r001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r001001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00101.c b/rtree-c/test/expected/functions/reduction/r001010.c similarity index 84% rename from rtree-c/test/expected/functions/reduction/r00101.c rename to rtree-c/test/expected/functions/reduction/r001010.c index f516cce4c7b006bfb00168121add189897d48016..a8be4151650c3d9264d817d27347baf77ad13642 100644 --- a/rtree-c/test/expected/functions/reduction/r00101.c +++ b/rtree-c/test/expected/functions/reduction/r001010.c @@ -3,6 +3,7 @@ // 1 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove expr statement at ("test/cases/small/functions.c": line 2) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r001010.c.hs b/rtree-c/test/expected/functions/reduction/r001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r001010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r001011.c b/rtree-c/test/expected/functions/reduction/r001011.c new file mode 100644 index 0000000000000000000000000000000000000000..482b030cca6c56a4295a233fb07fbd0f0f7b303e --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r001011.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ + a; +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r001011.c.hs b/rtree-c/test/expected/functions/reduction/r001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r001011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0011000.c b/rtree-c/test/expected/functions/reduction/r00110000.c similarity index 88% rename from rtree-c/test/expected/functions/reduction/r0011000.c rename to rtree-c/test/expected/functions/reduction/r00110000.c index 145db02f94be42e528f69179b0bfd97384722577..f7a9ac39ee4824822264b8e5edd416370785bfdd 100644 --- a/rtree-c/test/expected/functions/reduction/r0011000.c +++ b/rtree-c/test/expected/functions/reduction/r00110000.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r00110000.c.hs b/rtree-c/test/expected/functions/reduction/r00110000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00110000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00110001.c b/rtree-c/test/expected/functions/reduction/r00110001.c new file mode 100644 index 0000000000000000000000000000000000000000..b3958ef6cbb120e55cbfef0731f0a2c4c6088b15 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00110001.c @@ -0,0 +1,16 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r00110001.c.hs b/rtree-c/test/expected/functions/reduction/r00110001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00110001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0011001.c b/rtree-c/test/expected/functions/reduction/r0011001.c index f5dec9445b72cf0bd7291f9b5300102918d9baa1..9e67135902580c489f941f2687ee5826a4272306 100644 --- a/rtree-c/test/expected/functions/reduction/r0011001.c +++ b/rtree-c/test/expected/functions/reduction/r0011001.c @@ -2,8 +2,8 @@ // 0 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) // 0 remove return statement at ("test/cases/small/functions.c": line 9) -// 0 do without param at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) int f(int a) diff --git a/rtree-c/test/expected/functions/reduction/r0011001.c.hs b/rtree-c/test/expected/functions/reduction/r0011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00111.c b/rtree-c/test/expected/functions/reduction/r0011010.c similarity index 72% rename from rtree-c/test/expected/functions/reduction/r00111.c rename to rtree-c/test/expected/functions/reduction/r0011010.c index 2b415fed1bef11e5a88f76942250604c6cee5e4a..0112bf78d383fe1a50e6d1ed937c54e084594628 100644 --- a/rtree-c/test/expected/functions/reduction/r00111.c +++ b/rtree-c/test/expected/functions/reduction/r0011010.c @@ -2,7 +2,9 @@ // 0 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r0011010.c.hs b/rtree-c/test/expected/functions/reduction/r0011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0011011.c b/rtree-c/test/expected/functions/reduction/r0011011.c new file mode 100644 index 0000000000000000000000000000000000000000..8118804edb2f27dc0161a613fe8cf8f33273036e --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011011.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r0011011.c.hs b/rtree-c/test/expected/functions/reduction/r0011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00111000.c b/rtree-c/test/expected/functions/reduction/r00111000.c new file mode 100644 index 0000000000000000000000000000000000000000..12fb566c0b5ed17df98c64fb0356548986e9c460 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00111000.c @@ -0,0 +1,16 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int main() +{ + return f(42); +} diff --git a/rtree-c/test/expected/functions/reduction/r00111000.c.hs b/rtree-c/test/expected/functions/reduction/r00111000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00111000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r00111001.c b/rtree-c/test/expected/functions/reduction/r00111001.c new file mode 100644 index 0000000000000000000000000000000000000000..3ed3627dab4e6151ef101449a9cc954832cc3cbe --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00111001.c @@ -0,0 +1,16 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int f(int a) +{ +} +int main() +{ + return f(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r00111001.c.hs b/rtree-c/test/expected/functions/reduction/r00111001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r00111001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r001101.c b/rtree-c/test/expected/functions/reduction/r0011101.c similarity index 86% rename from rtree-c/test/expected/functions/reduction/r001101.c rename to rtree-c/test/expected/functions/reduction/r0011101.c index 77375d6bf98d9eb6726c84e45def99b2ce83c57a..34c0b22037d56758e54b551ec86e8c9431fe6f49 100644 --- a/rtree-c/test/expected/functions/reduction/r001101.c +++ b/rtree-c/test/expected/functions/reduction/r0011101.c @@ -2,6 +2,7 @@ // 0 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r0011101.c.hs b/rtree-c/test/expected/functions/reduction/r0011101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0011110.c b/rtree-c/test/expected/functions/reduction/r0011110.c new file mode 100644 index 0000000000000000000000000000000000000000..6a6a735d049e47e3397c84d8700c92aef7ea2929 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011110.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r0011110.c.hs b/rtree-c/test/expected/functions/reduction/r0011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0011111.c b/rtree-c/test/expected/functions/reduction/r0011111.c new file mode 100644 index 0000000000000000000000000000000000000000..913cb4a5fb9193b7d30a629ecea4a3c115025598 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011111.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove expr statement at ("test/cases/small/functions.c": line 2) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r0011111.c.hs b/rtree-c/test/expected/functions/reduction/r0011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0011111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01000.c b/rtree-c/test/expected/functions/reduction/r0100000.c similarity index 73% rename from rtree-c/test/expected/functions/reduction/r01000.c rename to rtree-c/test/expected/functions/reduction/r0100000.c index dc88096ff7a5fc7e4dbafac7cb7e7e046176f297..b226fa8f7bc8af5b488453752b436b65d3dc5dfc 100644 --- a/rtree-c/test/expected/functions/reduction/r01000.c +++ b/rtree-c/test/expected/functions/reduction/r0100000.c @@ -2,6 +2,8 @@ // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) int f() diff --git a/rtree-c/test/expected/functions/reduction/r0100000.c.hs b/rtree-c/test/expected/functions/reduction/r0100000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01001.c b/rtree-c/test/expected/functions/reduction/r01000010.c similarity index 64% rename from rtree-c/test/expected/functions/reduction/r01001.c rename to rtree-c/test/expected/functions/reduction/r01000010.c index 84b75cc3c10559caa96738f7963209970bbb070d..d44633671b4bd7cab6862176ff4e7a997b594a72 100644 --- a/rtree-c/test/expected/functions/reduction/r01001.c +++ b/rtree-c/test/expected/functions/reduction/r01000010.c @@ -2,7 +2,10 @@ // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f() { diff --git a/rtree-c/test/expected/functions/reduction/r01000010.c.hs b/rtree-c/test/expected/functions/reduction/r01000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01000011.c b/rtree-c/test/expected/functions/reduction/r01000011.c new file mode 100644 index 0000000000000000000000000000000000000000..ee3d907584617453ea1696917e4c4c4207dc2663 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000011.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01000011.c.hs b/rtree-c/test/expected/functions/reduction/r01000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0100010.c b/rtree-c/test/expected/functions/reduction/r0100010.c new file mode 100644 index 0000000000000000000000000000000000000000..443b15d24701111b0b75475abc2917d9b8169826 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100010.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0100010.c.hs b/rtree-c/test/expected/functions/reduction/r0100010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01000110.c b/rtree-c/test/expected/functions/reduction/r01000110.c new file mode 100644 index 0000000000000000000000000000000000000000..e876058b341d30dfc42b9ab6990bd0c582509c97 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01000110.c.hs b/rtree-c/test/expected/functions/reduction/r01000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01000111.c b/rtree-c/test/expected/functions/reduction/r01000111.c new file mode 100644 index 0000000000000000000000000000000000000000..14798b84678e44b36536d2af06fd8cb117cdd1d5 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000111.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01000111.c.hs b/rtree-c/test/expected/functions/reduction/r01000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01000111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0100100.c b/rtree-c/test/expected/functions/reduction/r0100100.c new file mode 100644 index 0000000000000000000000000000000000000000..e8cb96d3996386d0590f9eee8907cad20cc31ebb --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100100.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0100100.c.hs b/rtree-c/test/expected/functions/reduction/r0100100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01001010.c b/rtree-c/test/expected/functions/reduction/r01001010.c new file mode 100644 index 0000000000000000000000000000000000000000..7f1bee83cbaa99e49859ceec2e63bab5d39c2946 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001010.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01001010.c.hs b/rtree-c/test/expected/functions/reduction/r01001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01001011.c b/rtree-c/test/expected/functions/reduction/r01001011.c new file mode 100644 index 0000000000000000000000000000000000000000..8c561f85cff7cd8b14c14980f65fe51d2f92ee59 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001011.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01001011.c.hs b/rtree-c/test/expected/functions/reduction/r01001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0100110.c b/rtree-c/test/expected/functions/reduction/r0100110.c new file mode 100644 index 0000000000000000000000000000000000000000..265e0900adcd14f037b6109a89dc4a5c2f6da192 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0100110.c.hs b/rtree-c/test/expected/functions/reduction/r0100110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0100110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01001110.c b/rtree-c/test/expected/functions/reduction/r01001110.c new file mode 100644 index 0000000000000000000000000000000000000000..4fb5bc1d4c3b5496b3ec723364e7ae5781aa3fae --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01001110.c.hs b/rtree-c/test/expected/functions/reduction/r01001110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01001111.c b/rtree-c/test/expected/functions/reduction/r01001111.c new file mode 100644 index 0000000000000000000000000000000000000000..d0bbeeec969dd1fe9ccbc5def626a4fef38d6f9b --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001111.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01001111.c.hs b/rtree-c/test/expected/functions/reduction/r01001111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01001111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01010.c b/rtree-c/test/expected/functions/reduction/r0101000.c similarity index 73% rename from rtree-c/test/expected/functions/reduction/r01010.c rename to rtree-c/test/expected/functions/reduction/r0101000.c index a65ecc25d4a699ebf1a5d1c4de26affec3a2d372..e0b3f2a8bfd84cfbffab2206a0ab219a9058b66a 100644 --- a/rtree-c/test/expected/functions/reduction/r01010.c +++ b/rtree-c/test/expected/functions/reduction/r0101000.c @@ -2,6 +2,8 @@ // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) int f() diff --git a/rtree-c/test/expected/functions/reduction/r0101000.c.hs b/rtree-c/test/expected/functions/reduction/r0101000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01011.c b/rtree-c/test/expected/functions/reduction/r01010010.c similarity index 64% rename from rtree-c/test/expected/functions/reduction/r01011.c rename to rtree-c/test/expected/functions/reduction/r01010010.c index ca4938d28f98f1f68722f00d61f10bd0e1b7c7af..a3a0e5c87b70dfa98d6a99a8312883dbea15c618 100644 --- a/rtree-c/test/expected/functions/reduction/r01011.c +++ b/rtree-c/test/expected/functions/reduction/r01010010.c @@ -2,7 +2,10 @@ // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f() { diff --git a/rtree-c/test/expected/functions/reduction/r01010010.c.hs b/rtree-c/test/expected/functions/reduction/r01010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01010011.c b/rtree-c/test/expected/functions/reduction/r01010011.c new file mode 100644 index 0000000000000000000000000000000000000000..b9603a7e4cb3d6434f847ac39debb713275bebf5 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010011.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01010011.c.hs b/rtree-c/test/expected/functions/reduction/r01010011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0101010.c b/rtree-c/test/expected/functions/reduction/r0101010.c new file mode 100644 index 0000000000000000000000000000000000000000..24f5faf15e718d56ebda602f8e2eadd49a222e0e --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101010.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g() +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0101010.c.hs b/rtree-c/test/expected/functions/reduction/r0101010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01010110.c b/rtree-c/test/expected/functions/reduction/r01010110.c new file mode 100644 index 0000000000000000000000000000000000000000..a406fcfa7fd75253cfc967183611c36336c2ed8a --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01010110.c.hs b/rtree-c/test/expected/functions/reduction/r01010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01010111.c b/rtree-c/test/expected/functions/reduction/r01010111.c new file mode 100644 index 0000000000000000000000000000000000000000..3024a6fd29e0ec3600a64cd39efc69d022ee6483 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010111.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01010111.c.hs b/rtree-c/test/expected/functions/reduction/r01010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01010111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0101100.c b/rtree-c/test/expected/functions/reduction/r0101100.c new file mode 100644 index 0000000000000000000000000000000000000000..f6494af03200716592ee672e3575b971a580d9d9 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101100.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g() +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0101100.c.hs b/rtree-c/test/expected/functions/reduction/r0101100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01011010.c b/rtree-c/test/expected/functions/reduction/r01011010.c new file mode 100644 index 0000000000000000000000000000000000000000..900fe3a68f2aeab7d0f35e63da80f1b37c51d663 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011010.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01011010.c.hs b/rtree-c/test/expected/functions/reduction/r01011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01011011.c b/rtree-c/test/expected/functions/reduction/r01011011.c new file mode 100644 index 0000000000000000000000000000000000000000..0db36faf7cc9a9659059e595e8548209a7ff6577 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011011.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01011011.c.hs b/rtree-c/test/expected/functions/reduction/r01011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0101110.c b/rtree-c/test/expected/functions/reduction/r0101110.c new file mode 100644 index 0000000000000000000000000000000000000000..74e7f5f9e5fa2c50aaf048b21f7a414f26bd85a0 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int g() +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r0101110.c.hs b/rtree-c/test/expected/functions/reduction/r0101110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r0101110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01011110.c b/rtree-c/test/expected/functions/reduction/r01011110.c new file mode 100644 index 0000000000000000000000000000000000000000..c0112d8dbf36803541833a35b7118c3053ec03ec --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011110.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01011110.c.hs b/rtree-c/test/expected/functions/reduction/r01011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01011111.c b/rtree-c/test/expected/functions/reduction/r01011111.c new file mode 100644 index 0000000000000000000000000000000000000000..4ed5b05304390f4ca2e18382c623a4b3345c937a --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011111.c @@ -0,0 +1,18 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r01011111.c.hs b/rtree-c/test/expected/functions/reduction/r01011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01011111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0110.c b/rtree-c/test/expected/functions/reduction/r01100.c similarity index 81% rename from rtree-c/test/expected/functions/reduction/r0110.c rename to rtree-c/test/expected/functions/reduction/r01100.c index 17ab3522febe99909f37d36cd05353c2933996dd..12115d868c85832625a851f35a778083753c522a 100644 --- a/rtree-c/test/expected/functions/reduction/r0110.c +++ b/rtree-c/test/expected/functions/reduction/r01100.c @@ -1,6 +1,7 @@ // 0 remove function f at ("test/cases/small/functions.c": line 1) // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) // 0 remove return statement at ("test/cases/small/functions.c": line 9) int f() diff --git a/rtree-c/test/expected/functions/reduction/r01100.c.hs b/rtree-c/test/expected/functions/reduction/r01100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r0111.c b/rtree-c/test/expected/functions/reduction/r011010.c similarity index 67% rename from rtree-c/test/expected/functions/reduction/r0111.c rename to rtree-c/test/expected/functions/reduction/r011010.c index a55517c2f584803e6df59a5b577a4095a34ae25d..9b4eaf770d842daef4b4f7986177ebf8203eec63 100644 --- a/rtree-c/test/expected/functions/reduction/r0111.c +++ b/rtree-c/test/expected/functions/reduction/r011010.c @@ -1,7 +1,9 @@ // 0 remove function f at ("test/cases/small/functions.c": line 1) // 1 remove parameter at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int f() { diff --git a/rtree-c/test/expected/functions/reduction/r011010.c.hs b/rtree-c/test/expected/functions/reduction/r011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r011011.c b/rtree-c/test/expected/functions/reduction/r011011.c new file mode 100644 index 0000000000000000000000000000000000000000..3c0138d5fc8eb6cf5505926a6699f2488a9b4d92 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011011.c @@ -0,0 +1,13 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r011011.c.hs b/rtree-c/test/expected/functions/reduction/r011011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r01110.c b/rtree-c/test/expected/functions/reduction/r01110.c new file mode 100644 index 0000000000000000000000000000000000000000..eb43471231737bdb7bb5bf2329f261495b774601 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01110.c @@ -0,0 +1,13 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) + +int f() +{ +} +int main() +{ + return f(); +} diff --git a/rtree-c/test/expected/functions/reduction/r01110.c.hs b/rtree-c/test/expected/functions/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r01110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r011110.c b/rtree-c/test/expected/functions/reduction/r011110.c new file mode 100644 index 0000000000000000000000000000000000000000..37961a1d9dab546bb772c334cafb297afdba51ad --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011110.c @@ -0,0 +1,13 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r011110.c.hs b/rtree-c/test/expected/functions/reduction/r011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r011111.c b/rtree-c/test/expected/functions/reduction/r011111.c new file mode 100644 index 0000000000000000000000000000000000000000..b93e5cf0a6a91f05e838b510713a60d41ac3f331 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011111.c @@ -0,0 +1,13 @@ +// 0 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove parameter at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 1) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r011111.c.hs b/rtree-c/test/expected/functions/reduction/r011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r011111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r100000.c b/rtree-c/test/expected/functions/reduction/r1000000.c similarity index 86% rename from rtree-c/test/expected/functions/reduction/r100000.c rename to rtree-c/test/expected/functions/reduction/r1000000.c index 39b03b4387a8f1aa3233ef87681c401941b4cb75..bff2a37da5610469d1d17b6c37587a41d178fb0c 100644 --- a/rtree-c/test/expected/functions/reduction/r100000.c +++ b/rtree-c/test/expected/functions/reduction/r1000000.c @@ -1,6 +1,7 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r1000000.c.hs b/rtree-c/test/expected/functions/reduction/r1000000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1000000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1000001.c b/rtree-c/test/expected/functions/reduction/r1000001.c new file mode 100644 index 0000000000000000000000000000000000000000..164f0257ce1928124af4fa4a4ad4a39298d251b2 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1000001.c @@ -0,0 +1,15 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int g(int a) +{ +} +int main() +{ + return g(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r1000001.c.hs b/rtree-c/test/expected/functions/reduction/r1000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1000001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r100001.c b/rtree-c/test/expected/functions/reduction/r100001.c index da7a4288a8234fe70281138a2288cfc3ba577d66..2863daa7bbf1a8fa6d93a3e34d4191ea1d43b168 100644 --- a/rtree-c/test/expected/functions/reduction/r100001.c +++ b/rtree-c/test/expected/functions/reduction/r100001.c @@ -1,8 +1,8 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) -// 0 do without param at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) int g(int a) @@ -10,5 +10,5 @@ int g(int a) } int main() { - return g(0); + return 0; } diff --git a/rtree-c/test/expected/functions/reduction/r100001.c.hs b/rtree-c/test/expected/functions/reduction/r100001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1001.c b/rtree-c/test/expected/functions/reduction/r100010.c similarity index 68% rename from rtree-c/test/expected/functions/reduction/r1001.c rename to rtree-c/test/expected/functions/reduction/r100010.c index 51e8857f408887a3b818418d9cd3c29a4f65bb9e..9d5a4afc3edceda4a1597047680176616575e760 100644 --- a/rtree-c/test/expected/functions/reduction/r1001.c +++ b/rtree-c/test/expected/functions/reduction/r100010.c @@ -1,7 +1,9 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int g(int a) { diff --git a/rtree-c/test/expected/functions/reduction/r100010.c.hs b/rtree-c/test/expected/functions/reduction/r100010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r100011.c b/rtree-c/test/expected/functions/reduction/r100011.c new file mode 100644 index 0000000000000000000000000000000000000000..a658d65de7aac53a956f22df9e2711aa4fd0e6e1 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100011.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r100011.c.hs b/rtree-c/test/expected/functions/reduction/r100011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1001000.c b/rtree-c/test/expected/functions/reduction/r1001000.c new file mode 100644 index 0000000000000000000000000000000000000000..04b6aa21085c8045f7c7b0de4c2f0f163e5d1610 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1001000.c @@ -0,0 +1,15 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int g(int a) +{ +} +int main() +{ + return g(42); +} diff --git a/rtree-c/test/expected/functions/reduction/r1001000.c.hs b/rtree-c/test/expected/functions/reduction/r1001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1001000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1001001.c b/rtree-c/test/expected/functions/reduction/r1001001.c new file mode 100644 index 0000000000000000000000000000000000000000..363816ba97600d1c73ee92fa378d93284976d2e0 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1001001.c @@ -0,0 +1,15 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int g(int a) +{ +} +int main() +{ + return g(0); +} diff --git a/rtree-c/test/expected/functions/reduction/r1001001.c.hs b/rtree-c/test/expected/functions/reduction/r1001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1001001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r10001.c b/rtree-c/test/expected/functions/reduction/r100101.c similarity index 84% rename from rtree-c/test/expected/functions/reduction/r10001.c rename to rtree-c/test/expected/functions/reduction/r100101.c index 5d3a6ec23bc1324333e0f273b80efce35d69cb21..3e8eef39d0ec1cfb86c84e116d6eaf96d5481daa 100644 --- a/rtree-c/test/expected/functions/reduction/r10001.c +++ b/rtree-c/test/expected/functions/reduction/r100101.c @@ -1,6 +1,7 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r100101.c.hs b/rtree-c/test/expected/functions/reduction/r100101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r100110.c b/rtree-c/test/expected/functions/reduction/r100110.c new file mode 100644 index 0000000000000000000000000000000000000000..92d376d8f37ade8524268700429944e37dbf8ee8 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100110.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r100110.c.hs b/rtree-c/test/expected/functions/reduction/r100110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r100111.c b/rtree-c/test/expected/functions/reduction/r100111.c new file mode 100644 index 0000000000000000000000000000000000000000..80e33500e294a8e489864dae76e2cde90a6d2197 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100111.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 0 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g(int a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r100111.c.hs b/rtree-c/test/expected/functions/reduction/r100111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r100111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r10100.c b/rtree-c/test/expected/functions/reduction/r101000.c similarity index 84% rename from rtree-c/test/expected/functions/reduction/r10100.c rename to rtree-c/test/expected/functions/reduction/r101000.c index 81115f198eaed6b5c1928e6e2970e3a749b18855..7e065eabae2f82c9e0c16fcd44c39dcd6234832b 100644 --- a/rtree-c/test/expected/functions/reduction/r10100.c +++ b/rtree-c/test/expected/functions/reduction/r101000.c @@ -1,6 +1,7 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 0 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r101000.c.hs b/rtree-c/test/expected/functions/reduction/r101000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r10101.c b/rtree-c/test/expected/functions/reduction/r101001.c similarity index 84% rename from rtree-c/test/expected/functions/reduction/r10101.c rename to rtree-c/test/expected/functions/reduction/r101001.c index 2abbb2b7fe82eed1f8339bb213d19f548c5f6ea5..d3ad348e71f5dbab7441948e9c6f8c546445c25d 100644 --- a/rtree-c/test/expected/functions/reduction/r10101.c +++ b/rtree-c/test/expected/functions/reduction/r101001.c @@ -1,6 +1,7 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 0 remove return statement at ("test/cases/small/functions.c": line 9) // 1 do without param at ("test/cases/small/functions.c": line 9) diff --git a/rtree-c/test/expected/functions/reduction/r101001.c.hs b/rtree-c/test/expected/functions/reduction/r101001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1011.c b/rtree-c/test/expected/functions/reduction/r101010.c similarity index 67% rename from rtree-c/test/expected/functions/reduction/r1011.c rename to rtree-c/test/expected/functions/reduction/r101010.c index 348a8cf004f2160d82d80030f326262682021084..d36ae12bca893d8276d18eec2eddfa1bf56f0a58 100644 --- a/rtree-c/test/expected/functions/reduction/r1011.c +++ b/rtree-c/test/expected/functions/reduction/r101010.c @@ -1,7 +1,9 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 0 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int g() { diff --git a/rtree-c/test/expected/functions/reduction/r101010.c.hs b/rtree-c/test/expected/functions/reduction/r101010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r101011.c b/rtree-c/test/expected/functions/reduction/r101011.c new file mode 100644 index 0000000000000000000000000000000000000000..8501d660b86e7762d46da0fe9681a6510f35e3e0 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101011.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 0 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r101011.c.hs b/rtree-c/test/expected/functions/reduction/r101011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r101100.c b/rtree-c/test/expected/functions/reduction/r101100.c new file mode 100644 index 0000000000000000000000000000000000000000..41d79301adc0ce49f47724814db9ed6bd81efa1f --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101100.c @@ -0,0 +1,14 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 do without param at ("test/cases/small/functions.c": line 9) + +int g() +{ +} +int main() +{ + return g(); +} diff --git a/rtree-c/test/expected/functions/reduction/r101100.c.hs b/rtree-c/test/expected/functions/reduction/r101100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r101101.c b/rtree-c/test/expected/functions/reduction/r101101.c new file mode 100644 index 0000000000000000000000000000000000000000..68db56c6a2ae8b0b9c0b592561f279f4f55691b2 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101101.c @@ -0,0 +1,14 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 0 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 do without param at ("test/cases/small/functions.c": line 9) + +int g() +{ +} +int main() +{ + return 0; +} diff --git a/rtree-c/test/expected/functions/reduction/r101101.c.hs b/rtree-c/test/expected/functions/reduction/r101101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r101110.c b/rtree-c/test/expected/functions/reduction/r101110.c new file mode 100644 index 0000000000000000000000000000000000000000..add83b80142cfcaef37be58df358b98233fa1f85 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101110.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r101110.c.hs b/rtree-c/test/expected/functions/reduction/r101110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r101111.c b/rtree-c/test/expected/functions/reduction/r101111.c new file mode 100644 index 0000000000000000000000000000000000000000..53335d96795bd85f25ee07f7234b33c587fd086d --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101111.c @@ -0,0 +1,13 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 0 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove parameter at ("test/cases/small/functions.c": line 5) +// 1 remove empty compound at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int g() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r101111.c.hs b/rtree-c/test/expected/functions/reduction/r101111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r101111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r11000.c.hs b/rtree-c/test/expected/functions/reduction/r11000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r11000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r11001.c.hs b/rtree-c/test/expected/functions/reduction/r11001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r11001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1101.c.hs b/rtree-c/test/expected/functions/reduction/r1101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r111.c b/rtree-c/test/expected/functions/reduction/r1110.c similarity index 75% rename from rtree-c/test/expected/functions/reduction/r111.c rename to rtree-c/test/expected/functions/reduction/r1110.c index 58c45c0fb7b0b46fc9bc3cc134768a11cf465b20..bb933fa5ac102485aa902928bf273168a8115f09 100644 --- a/rtree-c/test/expected/functions/reduction/r111.c +++ b/rtree-c/test/expected/functions/reduction/r1110.c @@ -1,6 +1,7 @@ // 1 remove function f at ("test/cases/small/functions.c": line 1) // 1 remove function g at ("test/cases/small/functions.c": line 5) // 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 0 remove empty compound at ("test/cases/small/functions.c": line 8) int main() { diff --git a/rtree-c/test/expected/functions/reduction/r1110.c.hs b/rtree-c/test/expected/functions/reduction/r1110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/functions/reduction/r1111.c b/rtree-c/test/expected/functions/reduction/r1111.c new file mode 100644 index 0000000000000000000000000000000000000000..63f3bfbe7de6a72afd552e2b02c291801759d0e8 --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1111.c @@ -0,0 +1,8 @@ +// 1 remove function f at ("test/cases/small/functions.c": line 1) +// 1 remove function g at ("test/cases/small/functions.c": line 5) +// 1 remove return statement at ("test/cases/small/functions.c": line 9) +// 1 remove empty compound at ("test/cases/small/functions.c": line 8) + +int main() +{ +} diff --git a/rtree-c/test/expected/functions/reduction/r1111.c.hs b/rtree-c/test/expected/functions/reduction/r1111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..f1350f71ef6c5f5ad6c3f45bfed1a82f634c4dca --- /dev/null +++ b/rtree-c/test/expected/functions/reduction/r1111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CVar + ( Ident "a" 97 () ) () + ) + ) () + ) + ] () + ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "g" 103 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockStmt + ( CReturn + ( Just + ( CCall + ( CVar + ( Ident "f" 102 () ) () + ) + [ CCall + ( CVar + ( Ident "g" 103 () ) () + ) + [ CConst + ( CIntConst 42 () ) + ] () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/llvm-26760/reduction/p0.path b/rtree-c/test/expected/llvm-26760/reduction/p0.path index df502aea66a76f7a8c8ec68d1eaf8e8570283c4a..036e488463ddcc1f298ef95c72bf16d433ba1214 100644 --- a/rtree-c/test/expected/llvm-26760/reduction/p0.path +++ b/rtree-c/test/expected/llvm-26760/reduction/p0.path @@ -28,4 +28,5 @@ * reduce to right at ("test/cases/large/llvm-26760.c": line 24) * reduce to left at ("test/cases/large/llvm-26760.c": line 24) * reduce to right at ("test/cases/large/llvm-26760.c": line 24) +* remove empty compound at ("test/cases/large/llvm-26760.c": line 28) diff --git a/rtree-c/test/expected/llvm-26760/reduction/p1.path b/rtree-c/test/expected/llvm-26760/reduction/p1.path index 6d81e1a37e7ee393efb2cc85e0b184a3990c29a8..b5723830b6e5bd523ce4822bb31e388e2b7bd605 100644 --- a/rtree-c/test/expected/llvm-26760/reduction/p1.path +++ b/rtree-c/test/expected/llvm-26760/reduction/p1.path @@ -1,3 +1,4 @@ 1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) 1 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +* remove empty compound at ("test/cases/large/llvm-26760.c": line 28) diff --git a/rtree-c/test/expected/llvm-26760/reduction/p2.path b/rtree-c/test/expected/llvm-26760/reduction/p2.path new file mode 100644 index 0000000000000000000000000000000000000000..e8c90850cd10a7d18b1fc9db1e8884824d1e008f --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/p2.path @@ -0,0 +1,4 @@ +1 remove variable g_100 at ("test/cases/large/llvm-26760.c": line 6) +1 remove function func_33 at ("test/cases/large/llvm-26760.c": line 7) +1 remove empty compound at ("test/cases/large/llvm-26760.c": line 28) + diff --git a/rtree-c/test/expected/llvm-26760/reduction/x2.c b/rtree-c/test/expected/llvm-26760/reduction/x2.c new file mode 100644 index 0000000000000000000000000000000000000000..de5eef32927ce9e2d237cbd613ed255d62d04a89 --- /dev/null +++ b/rtree-c/test/expected/llvm-26760/reduction/x2.c @@ -0,0 +1,7 @@ +typedef signed int8_t; +typedef short int16_t; +typedef int int32_t; +typedef unsigned uint32_t; +int main() +{ +} diff --git a/rtree-c/test/expected/main/reduction/r.c b/rtree-c/test/expected/main/reduction/r.c deleted file mode 100644 index d3a1f6af4c831462788a2c6eae07e9be40f5b83d..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/main/reduction/r.c +++ /dev/null @@ -1,4 +0,0 @@ - -int main() -{ -} diff --git a/rtree-c/test/expected/main/reduction/r0.c b/rtree-c/test/expected/main/reduction/r0.c new file mode 100644 index 0000000000000000000000000000000000000000..88f1f2152f78e0616991bb6ce62c8a9d530984e0 --- /dev/null +++ b/rtree-c/test/expected/main/reduction/r0.c @@ -0,0 +1,5 @@ +// 0 remove empty compound at ("test/cases/small/main.c": line 2) + +int main() +{ +} diff --git a/rtree-c/test/expected/main/reduction/r0.c.hs b/rtree-c/test/expected/main/reduction/r0.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..0d620f07b0dae28f9a472758431f3e411d54b09b --- /dev/null +++ b/rtree-c/test/expected/main/reduction/r0.c.hs @@ -0,0 +1,17 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + ] () diff --git a/rtree-c/test/expected/main/reduction/r1.c b/rtree-c/test/expected/main/reduction/r1.c new file mode 100644 index 0000000000000000000000000000000000000000..dbd7ca4576106257054e78a299ca9397449d9697 --- /dev/null +++ b/rtree-c/test/expected/main/reduction/r1.c @@ -0,0 +1,5 @@ +// 1 remove empty compound at ("test/cases/small/main.c": line 2) + +int main() +{ +} diff --git a/rtree-c/test/expected/main/reduction/r1.c.hs b/rtree-c/test/expected/main/reduction/r1.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..0d620f07b0dae28f9a472758431f3e411d54b09b --- /dev/null +++ b/rtree-c/test/expected/main/reduction/r1.c.hs @@ -0,0 +1,17 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r00000.c.hs b/rtree-c/test/expected/struct/reduction/r00000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r00000.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r00001.c.hs b/rtree-c/test/expected/struct/reduction/r00001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r00001.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r00010.c.hs b/rtree-c/test/expected/struct/reduction/r00010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r00010.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r00011.c b/rtree-c/test/expected/struct/reduction/r000110.c similarity index 85% rename from rtree-c/test/expected/struct/reduction/r00011.c rename to rtree-c/test/expected/struct/reduction/r000110.c index d8242be758cb538893b8cfe55bde88b8aa8cd2bf..c96ab6b4ab265b447759032943e12cb86a2a7808 100644 --- a/rtree-c/test/expected/struct/reduction/r00011.c +++ b/rtree-c/test/expected/struct/reduction/r000110.c @@ -3,6 +3,7 @@ // 0 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) // 1 remove return statement at ("test/cases/small/struct.c": line 7) +// 0 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r000110.c.hs b/rtree-c/test/expected/struct/reduction/r000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r000110.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r10011.c b/rtree-c/test/expected/struct/reduction/r000111.c similarity index 65% rename from rtree-c/test/expected/struct/reduction/r10011.c rename to rtree-c/test/expected/struct/reduction/r000111.c index 5469ecc739dad3a1473300632332c8ef74241c5f..026c45475df1c7e9ee21440ffacedbce91d8f90b 100644 --- a/rtree-c/test/expected/struct/reduction/r10011.c +++ b/rtree-c/test/expected/struct/reduction/r000111.c @@ -1,12 +1,14 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 0 remove declaration at ("test/cases/small/struct.c": line 1) // 0 remove initializer at ("test/cases/small/struct.c": line 3) // 0 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) // 1 remove return statement at ("test/cases/small/struct.c": line 7) +// 1 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; -} p1 = { 0, 0 }; +}; +struct point p1 = { 0, 0 }; int main() { } diff --git a/rtree-c/test/expected/struct/reduction/r000111.c.hs b/rtree-c/test/expected/struct/reduction/r000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r000111.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r0010.c.hs b/rtree-c/test/expected/struct/reduction/r0010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r0010.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r0011.c b/rtree-c/test/expected/struct/reduction/r00110.c similarity index 82% rename from rtree-c/test/expected/struct/reduction/r0011.c rename to rtree-c/test/expected/struct/reduction/r00110.c index 7dfcde9214f9694f876bfd48210f2d0c48112696..4da04d6dc530b65ec19779acf3b6b9cfcff9d385 100644 --- a/rtree-c/test/expected/struct/reduction/r0011.c +++ b/rtree-c/test/expected/struct/reduction/r00110.c @@ -2,6 +2,7 @@ // 0 remove initializer at ("test/cases/small/struct.c": line 3) // 1 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) +// 0 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r00110.c.hs b/rtree-c/test/expected/struct/reduction/r00110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r00110.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r10101.c b/rtree-c/test/expected/struct/reduction/r00111.c similarity index 65% rename from rtree-c/test/expected/struct/reduction/r10101.c rename to rtree-c/test/expected/struct/reduction/r00111.c index 4e1f4fc58f9ccd671429762c7fe22591234706a9..c1731bde26d7c797bfcb7bdc5007cdee6e318914 100644 --- a/rtree-c/test/expected/struct/reduction/r10101.c +++ b/rtree-c/test/expected/struct/reduction/r00111.c @@ -1,8 +1,8 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 0 remove declaration at ("test/cases/small/struct.c": line 1) // 0 remove initializer at ("test/cases/small/struct.c": line 3) // 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove declaration at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) +// 1 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r00111.c.hs b/rtree-c/test/expected/struct/reduction/r00111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r00111.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r01000.c.hs b/rtree-c/test/expected/struct/reduction/r01000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r01000.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r01001.c.hs b/rtree-c/test/expected/struct/reduction/r01001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r01001.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r01010.c.hs b/rtree-c/test/expected/struct/reduction/r01010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r01010.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r01011.c b/rtree-c/test/expected/struct/reduction/r010110.c similarity index 85% rename from rtree-c/test/expected/struct/reduction/r01011.c rename to rtree-c/test/expected/struct/reduction/r010110.c index c4816c52b8748a17b32f497afefc3280f7b97490..816ba4713cc15b4a9f626e0415d5a3c2e4d6a8eb 100644 --- a/rtree-c/test/expected/struct/reduction/r01011.c +++ b/rtree-c/test/expected/struct/reduction/r010110.c @@ -3,6 +3,7 @@ // 0 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) // 1 remove return statement at ("test/cases/small/struct.c": line 7) +// 0 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r010110.c.hs b/rtree-c/test/expected/struct/reduction/r010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r010110.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r11011.c b/rtree-c/test/expected/struct/reduction/r010111.c similarity index 67% rename from rtree-c/test/expected/struct/reduction/r11011.c rename to rtree-c/test/expected/struct/reduction/r010111.c index 2aa7cdc800abdd0575664988ce1ec50cdc02402d..b678598153d66173e02626987dbe63c0b064bfbc 100644 --- a/rtree-c/test/expected/struct/reduction/r11011.c +++ b/rtree-c/test/expected/struct/reduction/r010111.c @@ -1,12 +1,14 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 0 remove declaration at ("test/cases/small/struct.c": line 1) // 1 remove initializer at ("test/cases/small/struct.c": line 3) // 0 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) // 1 remove return statement at ("test/cases/small/struct.c": line 7) +// 1 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; -} p1; +}; +struct point p1; int main() { } diff --git a/rtree-c/test/expected/struct/reduction/r010111.c.hs b/rtree-c/test/expected/struct/reduction/r010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r010111.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r0110.c.hs b/rtree-c/test/expected/struct/reduction/r0110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r0110.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r0111.c b/rtree-c/test/expected/struct/reduction/r01110.c similarity index 82% rename from rtree-c/test/expected/struct/reduction/r0111.c rename to rtree-c/test/expected/struct/reduction/r01110.c index 3f85b550340c7511fe41c902fceef2dee56cd85c..c17e7f2fd494ad63c87fea66c28000d663540b70 100644 --- a/rtree-c/test/expected/struct/reduction/r0111.c +++ b/rtree-c/test/expected/struct/reduction/r01110.c @@ -2,6 +2,7 @@ // 1 remove initializer at ("test/cases/small/struct.c": line 3) // 1 remove variable p1 at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) +// 0 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r01110.c.hs b/rtree-c/test/expected/struct/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r01110.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r11101.c b/rtree-c/test/expected/struct/reduction/r01111.c similarity index 65% rename from rtree-c/test/expected/struct/reduction/r11101.c rename to rtree-c/test/expected/struct/reduction/r01111.c index 95b2c716bd1a4657e318d8658b394caa3ac25c58..ee1551096d925356ed60379a11a8c1df9072d6bb 100644 --- a/rtree-c/test/expected/struct/reduction/r11101.c +++ b/rtree-c/test/expected/struct/reduction/r01111.c @@ -1,8 +1,8 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 0 remove declaration at ("test/cases/small/struct.c": line 1) // 1 remove initializer at ("test/cases/small/struct.c": line 3) // 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove declaration at ("test/cases/small/struct.c": line 3) // 1 remove variable p2 at ("test/cases/small/struct.c": line 6) +// 1 remove empty compound at ("test/cases/small/struct.c": line 5) struct point { int x; int y; diff --git a/rtree-c/test/expected/struct/reduction/r01111.c.hs b/rtree-c/test/expected/struct/reduction/r01111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r01111.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r10.c b/rtree-c/test/expected/struct/reduction/r10.c new file mode 100644 index 0000000000000000000000000000000000000000..624856a49bf8dfef8c59e59d89eed40ed5709122 --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r10.c @@ -0,0 +1,6 @@ +// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 0 remove empty compound at ("test/cases/small/struct.c": line 5) + +int main() +{ +} diff --git a/rtree-c/test/expected/struct/reduction/r10.c.hs b/rtree-c/test/expected/struct/reduction/r10.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r10.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r10000.c b/rtree-c/test/expected/struct/reduction/r10000.c deleted file mode 100644 index 5f24f5d3f7c877d636040a38a276973083926336..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r10000.c +++ /dev/null @@ -1,14 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1 = { 0, 0 }; -int main() -{ - struct point p2; - return p1.x; -} diff --git a/rtree-c/test/expected/struct/reduction/r10001.c b/rtree-c/test/expected/struct/reduction/r10001.c deleted file mode 100644 index 26d3d480099184149e814177db758664deb3577a..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r10001.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 1 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1 = { 0, 0 }; -int main() -{ - struct point p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r10010.c b/rtree-c/test/expected/struct/reduction/r10010.c deleted file mode 100644 index 6bc2399c6b461b03e95926dae1e3d15d95dfcafc..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r10010.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1 = { 0, 0 }; -int main() -{ - return p1.x; -} diff --git a/rtree-c/test/expected/struct/reduction/r10100.c b/rtree-c/test/expected/struct/reduction/r10100.c deleted file mode 100644 index 7b5ca3ca2b3303b468984b202e4653f81fb5f5d3..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r10100.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove declaration at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) - -struct point { - int x; int y; -}; -int main() -{ - struct point p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r10110.c b/rtree-c/test/expected/struct/reduction/r10110.c deleted file mode 100644 index 628ff25f9336cad3a6c82f879e9816e89d2b5327..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r10110.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) - -int main() -{ - struct point { - int x; int y; - } p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r101110.c b/rtree-c/test/expected/struct/reduction/r101110.c deleted file mode 100644 index 5fa60aff792409a5ce1aec509ea5291bf8516ceb..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r101110.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove declaration at ("test/cases/small/struct.c": line 6) - -int main() -{ - struct point { - int x; int y; - }; -} diff --git a/rtree-c/test/expected/struct/reduction/r101111.c b/rtree-c/test/expected/struct/reduction/r101111.c deleted file mode 100644 index 81a3361597ceeff9a90e7ff7ca539cc73e94f6cc..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r101111.c +++ /dev/null @@ -1,10 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 0 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 1 remove declaration at ("test/cases/small/struct.c": line 6) - -int main() -{ -} diff --git a/rtree-c/test/expected/struct/reduction/r11.c b/rtree-c/test/expected/struct/reduction/r11.c new file mode 100644 index 0000000000000000000000000000000000000000..d947367214a02c965758d85245bc4e248cef4b44 --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r11.c @@ -0,0 +1,6 @@ +// 1 remove declaration at ("test/cases/small/struct.c": line 1) +// 1 remove empty compound at ("test/cases/small/struct.c": line 5) + +int main() +{ +} diff --git a/rtree-c/test/expected/struct/reduction/r11.c.hs b/rtree-c/test/expected/struct/reduction/r11.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b37197c052a13f45a05b125a4e86842cb81e145e --- /dev/null +++ b/rtree-c/test/expected/struct/reduction/r11.c.hs @@ -0,0 +1,126 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) + ( Just + [ CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + , CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "y" 121 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] + ) [] () + ) () + ) + ] [] () + ) + , CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p1" 6384 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList + [ + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + , + ( [] + , CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ] + ) () + ) + ) Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "point" 232421476 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "p2" 6512 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CMember + ( CVar + ( Ident "p1" 6384 () ) () + ) + ( Ident "x" 120 () ) False () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/struct/reduction/r11000.c b/rtree-c/test/expected/struct/reduction/r11000.c deleted file mode 100644 index ad29f2cbabebd81905dd71b83b11850ab60464f3..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r11000.c +++ /dev/null @@ -1,14 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1; -int main() -{ - struct point p2; - return p1.x; -} diff --git a/rtree-c/test/expected/struct/reduction/r11001.c b/rtree-c/test/expected/struct/reduction/r11001.c deleted file mode 100644 index ad64bd661639fd85214888fa7e680393df6c0f5b..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r11001.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 1 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1; -int main() -{ - struct point p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r11010.c b/rtree-c/test/expected/struct/reduction/r11010.c deleted file mode 100644 index 6e462e9b882e2f6ad649343ebe8e6292ca95a79c..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r11010.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 0 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove return statement at ("test/cases/small/struct.c": line 7) - -struct point { - int x; int y; -} p1; -int main() -{ - return p1.x; -} diff --git a/rtree-c/test/expected/struct/reduction/r11100.c b/rtree-c/test/expected/struct/reduction/r11100.c deleted file mode 100644 index 24ab4dddb90002c5a3ba48c082ac7f832fcfb479..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r11100.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 0 remove declaration at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) - -struct point { - int x; int y; -}; -int main() -{ - struct point p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r11110.c b/rtree-c/test/expected/struct/reduction/r11110.c deleted file mode 100644 index b5434f3f372ce4b0c97b5c8fb08061851cd19316..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r11110.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 0 remove variable p2 at ("test/cases/small/struct.c": line 6) - -int main() -{ - struct point { - int x; int y; - } p2; -} diff --git a/rtree-c/test/expected/struct/reduction/r111110.c b/rtree-c/test/expected/struct/reduction/r111110.c deleted file mode 100644 index ebe40cbde278ea8d2e4faf33da5c415407e56b39..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r111110.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 0 remove declaration at ("test/cases/small/struct.c": line 6) - -int main() -{ - struct point { - int x; int y; - }; -} diff --git a/rtree-c/test/expected/struct/reduction/r111111.c b/rtree-c/test/expected/struct/reduction/r111111.c deleted file mode 100644 index fc0173007a1840aba20e146a33e84718868808de..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/struct/reduction/r111111.c +++ /dev/null @@ -1,10 +0,0 @@ -// 1 remove declaration at ("test/cases/small/struct.c": line 1) -// 1 remove initializer at ("test/cases/small/struct.c": line 3) -// 1 remove variable p1 at ("test/cases/small/struct.c": line 3) -// 1 remove declaration at ("test/cases/small/struct.c": line 3) -// 1 remove variable p2 at ("test/cases/small/struct.c": line 6) -// 1 remove declaration at ("test/cases/small/struct.c": line 6) - -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/main.c b/rtree-c/test/expected/structfn/main.c index 0f9a21fc495fc1f62616cbb997a57f686c9b50b7..2b7618ccc797a0dfd0d3dad286a4ea15243f77cc 100644 --- a/rtree-c/test/expected/structfn/main.c +++ b/rtree-c/test/expected/structfn/main.c @@ -1,9 +1,9 @@ struct S0 { }; -struct S0 g0 = { }; void fn(struct S0 a) { } int main() { + struct S0 g0 = { }; fn(g0); } diff --git a/rtree-c/test/expected/structfn/reduction/r000000.c b/rtree-c/test/expected/structfn/reduction/r0000000.c similarity index 69% rename from rtree-c/test/expected/structfn/reduction/r000000.c rename to rtree-c/test/expected/structfn/reduction/r0000000.c index 4818fbfacacedc15c89cb6b71a62fbdbe99122fa..3e57168245ede513a5a6d0e0d46ca06ebb365ba1 100644 --- a/rtree-c/test/expected/structfn/reduction/r000000.c +++ b/rtree-c/test/expected/structfn/reduction/r0000000.c @@ -1,16 +1,17 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0 = { }; void fn(struct S0 a) { } int main() { + struct S0 g0 = { }; fn(g0); } diff --git a/rtree-c/test/expected/structfn/reduction/r0000000.c.hs b/rtree-c/test/expected/structfn/reduction/r0000000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r000001.c b/rtree-c/test/expected/structfn/reduction/r0000001.c similarity index 69% rename from rtree-c/test/expected/structfn/reduction/r000001.c rename to rtree-c/test/expected/structfn/reduction/r0000001.c index 7b0dc934848448a4629838a6d41b343aa49eb1da..981450d33be568c77c8f7da239b547b25b18b074 100644 --- a/rtree-c/test/expected/structfn/reduction/r000001.c +++ b/rtree-c/test/expected/structfn/reduction/r0000001.c @@ -1,15 +1,16 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0 = { }; void fn(struct S0 a) { } int main() { + struct S0 g0 = { }; } diff --git a/rtree-c/test/expected/structfn/reduction/r0000001.c.hs b/rtree-c/test/expected/structfn/reduction/r0000001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r101000.c b/rtree-c/test/expected/structfn/reduction/r0000010.c similarity index 60% rename from rtree-c/test/expected/structfn/reduction/r101000.c rename to rtree-c/test/expected/structfn/reduction/r0000010.c index 40e99c0044b49d2e80a4368c452b8f85ed320937..65124131f18c8d8b328b57054b16178ac137c6a8 100644 --- a/rtree-c/test/expected/structfn/reduction/r101000.c +++ b/rtree-c/test/expected/structfn/reduction/r0000010.c @@ -1,9 +1,10 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn(struct S0 a) diff --git a/rtree-c/test/expected/structfn/reduction/r0000010.c.hs b/rtree-c/test/expected/structfn/reduction/r0000010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00100.c b/rtree-c/test/expected/structfn/reduction/r0000011.c similarity index 60% rename from rtree-c/test/expected/structfn/reduction/r00100.c rename to rtree-c/test/expected/structfn/reduction/r0000011.c index 6645ae0cb2a27a3ca691f2160268fa0e27d59d70..a85e07fe381c2a0b9f9344a956ef66f3d505e33e 100644 --- a/rtree-c/test/expected/structfn/reduction/r00100.c +++ b/rtree-c/test/expected/structfn/reduction/r0000011.c @@ -1,8 +1,10 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn(struct S0 a) diff --git a/rtree-c/test/expected/structfn/reduction/r0000011.c.hs b/rtree-c/test/expected/structfn/reduction/r0000011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r110000.c b/rtree-c/test/expected/structfn/reduction/r0000100.c similarity index 56% rename from rtree-c/test/expected/structfn/reduction/r110000.c rename to rtree-c/test/expected/structfn/reduction/r0000100.c index 08082c87036633f5d6431b0836234f41bd46ddd7..22e31a3d6340bf039710766c92ae8417adbb560f 100644 --- a/rtree-c/test/expected/structfn/reduction/r110000.c +++ b/rtree-c/test/expected/structfn/reduction/r0000100.c @@ -1,15 +1,17 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0; +struct S0 { }; void fn(struct S0 a) { } int main() { + struct S0 g0; fn(g0); } diff --git a/rtree-c/test/expected/structfn/reduction/r0000100.c.hs b/rtree-c/test/expected/structfn/reduction/r0000100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r110001.c b/rtree-c/test/expected/structfn/reduction/r0000101.c similarity index 55% rename from rtree-c/test/expected/structfn/reduction/r110001.c rename to rtree-c/test/expected/structfn/reduction/r0000101.c index 755f0aaf1dd64956c1e175cd972006ca3f92ae8c..e899a6f33cbbdcb32185f60653b5440674ea5ccb 100644 --- a/rtree-c/test/expected/structfn/reduction/r110001.c +++ b/rtree-c/test/expected/structfn/reduction/r0000101.c @@ -1,14 +1,16 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0; +struct S0 { }; void fn(struct S0 a) { } int main() { + struct S0 g0; } diff --git a/rtree-c/test/expected/structfn/reduction/r0000101.c.hs b/rtree-c/test/expected/structfn/reduction/r0000101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r01100.c b/rtree-c/test/expected/structfn/reduction/r0000110.c similarity index 60% rename from rtree-c/test/expected/structfn/reduction/r01100.c rename to rtree-c/test/expected/structfn/reduction/r0000110.c index 9b4032ab476d06a07da7e6b7500574d45a1f2920..4ea2822614f754ce4b16c3e138b852e442cb1172 100644 --- a/rtree-c/test/expected/structfn/reduction/r01100.c +++ b/rtree-c/test/expected/structfn/reduction/r0000110.c @@ -1,8 +1,10 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn(struct S0 a) diff --git a/rtree-c/test/expected/structfn/reduction/r0000110.c.hs b/rtree-c/test/expected/structfn/reduction/r0000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r111000.c b/rtree-c/test/expected/structfn/reduction/r0000111.c similarity index 60% rename from rtree-c/test/expected/structfn/reduction/r111000.c rename to rtree-c/test/expected/structfn/reduction/r0000111.c index 1f65dcdee287194249edf0b3c8c93eae43578248..1bc7b92813a2ef243499eedb111baea3855b3853 100644 --- a/rtree-c/test/expected/structfn/reduction/r111000.c +++ b/rtree-c/test/expected/structfn/reduction/r0000111.c @@ -1,9 +1,10 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn(struct S0 a) diff --git a/rtree-c/test/expected/structfn/reduction/r0000111.c.hs b/rtree-c/test/expected/structfn/reduction/r0000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0000111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r000100.c b/rtree-c/test/expected/structfn/reduction/r000100.c deleted file mode 100644 index 8bd0f08d909fdef110abc5a74622505bf7be8679..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r000100.c +++ /dev/null @@ -1,13 +0,0 @@ -// 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 0 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { }; -struct S0 g0 = { }; -int main() -{ - g0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r100000.c b/rtree-c/test/expected/structfn/reduction/r0001000.c similarity index 55% rename from rtree-c/test/expected/structfn/reduction/r100000.c rename to rtree-c/test/expected/structfn/reduction/r0001000.c index bc6043bd2882390870b58dc7ac392be98fcd0423..db57c4131aeed78d2017d97c6b1969b4c15a2d9c 100644 --- a/rtree-c/test/expected/structfn/reduction/r100000.c +++ b/rtree-c/test/expected/structfn/reduction/r0001000.c @@ -1,15 +1,17 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0 = { }; +struct S0 { }; void fn(struct S0 a) { } int main() { + struct S0 g0 = { }; fn(g0); } diff --git a/rtree-c/test/expected/structfn/reduction/r0001000.c.hs b/rtree-c/test/expected/structfn/reduction/r0001000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r100001.c b/rtree-c/test/expected/structfn/reduction/r0001001.c similarity index 54% rename from rtree-c/test/expected/structfn/reduction/r100001.c rename to rtree-c/test/expected/structfn/reduction/r0001001.c index 77e6f7f4f20690e5b6ee2fda19b3f69e44c5138f..01374e1e342bbcfc126d1de0dc3da5d467e398fe 100644 --- a/rtree-c/test/expected/structfn/reduction/r100001.c +++ b/rtree-c/test/expected/structfn/reduction/r0001001.c @@ -1,14 +1,16 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0 = { }; +struct S0 { }; void fn(struct S0 a) { } int main() { + struct S0 g0 = { }; } diff --git a/rtree-c/test/expected/structfn/reduction/r0001001.c.hs b/rtree-c/test/expected/structfn/reduction/r0001001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r000101.c b/rtree-c/test/expected/structfn/reduction/r000101.c deleted file mode 100644 index 751fd99e607b97c6d26fdfeec81c365ddac1fa63..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r000101.c +++ /dev/null @@ -1,13 +0,0 @@ -// 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 1 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { }; -struct S0 g0 = { }; -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r0001010.c b/rtree-c/test/expected/structfn/reduction/r0001010.c new file mode 100644 index 0000000000000000000000000000000000000000..7c5dfc5396fe4b2774c39cf639c97e05ecc06cd1 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001010.c @@ -0,0 +1,15 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001010.c.hs b/rtree-c/test/expected/structfn/reduction/r0001010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0001011.c b/rtree-c/test/expected/structfn/reduction/r0001011.c new file mode 100644 index 0000000000000000000000000000000000000000..4d85154b140a727877f36baa5552e1acb606a69b --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001011.c @@ -0,0 +1,15 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001011.c.hs b/rtree-c/test/expected/structfn/reduction/r0001011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0001100.c b/rtree-c/test/expected/structfn/reduction/r0001100.c new file mode 100644 index 0000000000000000000000000000000000000000..a03b0497e1cdad03aa8746378eebfd45b666c153 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001100.c @@ -0,0 +1,17 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ + struct S0 g0; + fn(g0); +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001100.c.hs b/rtree-c/test/expected/structfn/reduction/r0001100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0001101.c b/rtree-c/test/expected/structfn/reduction/r0001101.c new file mode 100644 index 0000000000000000000000000000000000000000..4f707f5b17c639dcc29d1d977ac9f43749c91bf3 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001101.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ + struct S0 g0; +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001101.c.hs b/rtree-c/test/expected/structfn/reduction/r0001101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0001110.c b/rtree-c/test/expected/structfn/reduction/r0001110.c new file mode 100644 index 0000000000000000000000000000000000000000..3bdc2c15ca0c5fee63feed518d5f59b311996ac8 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001110.c @@ -0,0 +1,15 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001110.c.hs b/rtree-c/test/expected/structfn/reduction/r0001110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0001111.c b/rtree-c/test/expected/structfn/reduction/r0001111.c new file mode 100644 index 0000000000000000000000000000000000000000..8cc4adab6f2999556666fe0951a8b804039089ca --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001111.c @@ -0,0 +1,15 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn(struct S0 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r0001111.c.hs b/rtree-c/test/expected/structfn/reduction/r0001111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0001111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r000010.c b/rtree-c/test/expected/structfn/reduction/r0010000.c similarity index 69% rename from rtree-c/test/expected/structfn/reduction/r000010.c rename to rtree-c/test/expected/structfn/reduction/r0010000.c index 0378bafac8f9f9c621ff5d6a709679ff4702a74b..a13f5c0ea4e6c787f3e849ab8ce949bd6914f34b 100644 --- a/rtree-c/test/expected/structfn/reduction/r000010.c +++ b/rtree-c/test/expected/structfn/reduction/r0010000.c @@ -1,16 +1,17 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0 = { }; void fn() { } int main() { + struct S0 g0 = { }; fn(); } diff --git a/rtree-c/test/expected/structfn/reduction/r0010000.c.hs b/rtree-c/test/expected/structfn/reduction/r0010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r000011.c b/rtree-c/test/expected/structfn/reduction/r0010001.c similarity index 68% rename from rtree-c/test/expected/structfn/reduction/r000011.c rename to rtree-c/test/expected/structfn/reduction/r0010001.c index 99337bbb2f82d571bb6f630208e2274b992a0e6c..a2b711208525b1c999c70ca514204b82447efa98 100644 --- a/rtree-c/test/expected/structfn/reduction/r000011.c +++ b/rtree-c/test/expected/structfn/reduction/r0010001.c @@ -1,15 +1,16 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0 = { }; void fn() { } int main() { + struct S0 g0 = { }; } diff --git a/rtree-c/test/expected/structfn/reduction/r0010001.c.hs b/rtree-c/test/expected/structfn/reduction/r0010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r1010010.c b/rtree-c/test/expected/structfn/reduction/r0010010.c similarity index 72% rename from rtree-c/test/expected/structfn/reduction/r1010010.c rename to rtree-c/test/expected/structfn/reduction/r0010010.c index d60649aa0fd3fc7456faecfc15f38d5aa81deb11..90f48fd318e804fcfd9726a8d9b0d6148ff6f7c1 100644 --- a/rtree-c/test/expected/structfn/reduction/r1010010.c +++ b/rtree-c/test/expected/structfn/reduction/r0010010.c @@ -1,10 +1,10 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r0010010.c.hs b/rtree-c/test/expected/structfn/reduction/r0010010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r001011.c b/rtree-c/test/expected/structfn/reduction/r00100110.c similarity index 63% rename from rtree-c/test/expected/structfn/reduction/r001011.c rename to rtree-c/test/expected/structfn/reduction/r00100110.c index e2c2a118d7b6e9c57ccc0960ebaf16e10719199b..aaa77aabc269f7a778da9374cecba22d100a2814 100644 --- a/rtree-c/test/expected/structfn/reduction/r001011.c +++ b/rtree-c/test/expected/structfn/reduction/r00100110.c @@ -1,9 +1,11 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r00100110.c.hs b/rtree-c/test/expected/structfn/reduction/r00100110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00100110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r1010011.c b/rtree-c/test/expected/structfn/reduction/r00100111.c similarity index 63% rename from rtree-c/test/expected/structfn/reduction/r1010011.c rename to rtree-c/test/expected/structfn/reduction/r00100111.c index f493de83efee09d3c333e0dd0d25d951f11b8e4c..673794b767a4441eead2c18411d035ff621ff7a2 100644 --- a/rtree-c/test/expected/structfn/reduction/r1010011.c +++ b/rtree-c/test/expected/structfn/reduction/r00100111.c @@ -1,10 +1,11 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r00100111.c.hs b/rtree-c/test/expected/structfn/reduction/r00100111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00100111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010010.c b/rtree-c/test/expected/structfn/reduction/r0010100.c similarity index 69% rename from rtree-c/test/expected/structfn/reduction/r010010.c rename to rtree-c/test/expected/structfn/reduction/r0010100.c index db4ed44db4fe25394457f0da25090de909761faa..0a0c25b0866e63edbce8b7a3c1ae2960af8b9a56 100644 --- a/rtree-c/test/expected/structfn/reduction/r010010.c +++ b/rtree-c/test/expected/structfn/reduction/r0010100.c @@ -1,16 +1,17 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; void fn() { } int main() { + struct S0 g0; fn(); } diff --git a/rtree-c/test/expected/structfn/reduction/r0010100.c.hs b/rtree-c/test/expected/structfn/reduction/r0010100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010011.c b/rtree-c/test/expected/structfn/reduction/r0010101.c similarity index 69% rename from rtree-c/test/expected/structfn/reduction/r010011.c rename to rtree-c/test/expected/structfn/reduction/r0010101.c index 4415f22c2e7bcf1327589eb04daa5311cb000583..a318e80c3c03a0d90b789685ee87028ee8eeafb9 100644 --- a/rtree-c/test/expected/structfn/reduction/r010011.c +++ b/rtree-c/test/expected/structfn/reduction/r0010101.c @@ -1,15 +1,16 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; void fn() { } int main() { + struct S0 g0; } diff --git a/rtree-c/test/expected/structfn/reduction/r0010101.c.hs b/rtree-c/test/expected/structfn/reduction/r0010101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r1110010.c b/rtree-c/test/expected/structfn/reduction/r0010110.c similarity index 72% rename from rtree-c/test/expected/structfn/reduction/r1110010.c rename to rtree-c/test/expected/structfn/reduction/r0010110.c index 4b369e10c4d8f3e1563a99b5d09462a9184f44a1..9f7a2fdf5b7ce8509dedee257ade9eb004e15483 100644 --- a/rtree-c/test/expected/structfn/reduction/r1110010.c +++ b/rtree-c/test/expected/structfn/reduction/r0010110.c @@ -1,10 +1,10 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r0010110.c.hs b/rtree-c/test/expected/structfn/reduction/r0010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0010110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r1110011.c b/rtree-c/test/expected/structfn/reduction/r00101110.c similarity index 63% rename from rtree-c/test/expected/structfn/reduction/r1110011.c rename to rtree-c/test/expected/structfn/reduction/r00101110.c index 2c9e59edc9ee0055def2e42f43e38f7158065777..a172bc1e984f625fd265fca3228d8402c63faaeb 100644 --- a/rtree-c/test/expected/structfn/reduction/r1110011.c +++ b/rtree-c/test/expected/structfn/reduction/r00101110.c @@ -1,10 +1,11 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r00101110.c.hs b/rtree-c/test/expected/structfn/reduction/r00101110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00101110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r011011.c b/rtree-c/test/expected/structfn/reduction/r00101111.c similarity index 63% rename from rtree-c/test/expected/structfn/reduction/r011011.c rename to rtree-c/test/expected/structfn/reduction/r00101111.c index b8288d5e9d970245615071aad45812faf79427a1..9d1b94dfb8e155575c86437d9702122d7668257f 100644 --- a/rtree-c/test/expected/structfn/reduction/r011011.c +++ b/rtree-c/test/expected/structfn/reduction/r00101111.c @@ -1,9 +1,11 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r00101111.c.hs b/rtree-c/test/expected/structfn/reduction/r00101111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00101111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0011000.c b/rtree-c/test/expected/structfn/reduction/r0011000.c new file mode 100644 index 0000000000000000000000000000000000000000..3d8d1ea81fd3d949fe7ed6ae5e2b8229907d5fd1 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011000.c @@ -0,0 +1,17 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn() +{ +} +int main() +{ + struct S0 g0 = { }; + fn(); +} diff --git a/rtree-c/test/expected/structfn/reduction/r0011000.c.hs b/rtree-c/test/expected/structfn/reduction/r0011000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0011001.c b/rtree-c/test/expected/structfn/reduction/r0011001.c new file mode 100644 index 0000000000000000000000000000000000000000..27a50c22d680cf4d1dee979368b653840cfb1b6a --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011001.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn() +{ +} +int main() +{ + struct S0 g0 = { }; +} diff --git a/rtree-c/test/expected/structfn/reduction/r0011001.c.hs b/rtree-c/test/expected/structfn/reduction/r0011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r001010.c b/rtree-c/test/expected/structfn/reduction/r0011010.c similarity index 72% rename from rtree-c/test/expected/structfn/reduction/r001010.c rename to rtree-c/test/expected/structfn/reduction/r0011010.c index fdbf7cf6300d23938c9fa99e2cf24ffc96bb16e8..78433e47b3f3fe2ac44a8b41b2f50e4e9ce8c8ad 100644 --- a/rtree-c/test/expected/structfn/reduction/r001010.c +++ b/rtree-c/test/expected/structfn/reduction/r0011010.c @@ -1,9 +1,10 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r0011010.c.hs b/rtree-c/test/expected/structfn/reduction/r0011010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00110110.c b/rtree-c/test/expected/structfn/reduction/r00110110.c new file mode 100644 index 0000000000000000000000000000000000000000..f9d37d57b31b721d7e511c5aa9f3e96f8d95b1e5 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00110110.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r00110110.c.hs b/rtree-c/test/expected/structfn/reduction/r00110110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00110110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00110111.c b/rtree-c/test/expected/structfn/reduction/r00110111.c new file mode 100644 index 0000000000000000000000000000000000000000..880e5169ee07fd344b8490c0c3736d1d97ef0181 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00110111.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r00110111.c.hs b/rtree-c/test/expected/structfn/reduction/r00110111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00110111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0011100.c b/rtree-c/test/expected/structfn/reduction/r0011100.c new file mode 100644 index 0000000000000000000000000000000000000000..6e7740e320bef43f31118d5f127315a0c643daf6 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011100.c @@ -0,0 +1,17 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn() +{ +} +int main() +{ + struct S0 g0; + fn(); +} diff --git a/rtree-c/test/expected/structfn/reduction/r0011100.c.hs b/rtree-c/test/expected/structfn/reduction/r0011100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011100.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r0011101.c b/rtree-c/test/expected/structfn/reduction/r0011101.c new file mode 100644 index 0000000000000000000000000000000000000000..d0f5fda7d2dc31ca3efb7860383baae4f0e91aef --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011101.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) + +struct S0 { }; +void fn() +{ +} +int main() +{ + struct S0 g0; +} diff --git a/rtree-c/test/expected/structfn/reduction/r0011101.c.hs b/rtree-c/test/expected/structfn/reduction/r0011101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r011010.c b/rtree-c/test/expected/structfn/reduction/r0011110.c similarity index 72% rename from rtree-c/test/expected/structfn/reduction/r011010.c rename to rtree-c/test/expected/structfn/reduction/r0011110.c index c72c3e47bb2a40500b4e6d03477cdfec3eda9072..cb725e124457ff288e493de5b12cd8452be47a86 100644 --- a/rtree-c/test/expected/structfn/reduction/r011010.c +++ b/rtree-c/test/expected/structfn/reduction/r0011110.c @@ -1,9 +1,10 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; void fn() diff --git a/rtree-c/test/expected/structfn/reduction/r0011110.c.hs b/rtree-c/test/expected/structfn/reduction/r0011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r0011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00111110.c b/rtree-c/test/expected/structfn/reduction/r00111110.c new file mode 100644 index 0000000000000000000000000000000000000000..4df328981747ff257f478c933b83ebb784b74308 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00111110.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r00111110.c.hs b/rtree-c/test/expected/structfn/reduction/r00111110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00111110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00111111.c b/rtree-c/test/expected/structfn/reduction/r00111111.c new file mode 100644 index 0000000000000000000000000000000000000000..b7a92cbea3437c8afeea938c49c74b7cbcffa893 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00111111.c @@ -0,0 +1,16 @@ +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove parameter at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) + +struct S0 { }; +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r00111111.c.hs b/rtree-c/test/expected/structfn/reduction/r00111111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r00111111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010000.c b/rtree-c/test/expected/structfn/reduction/r010000.c index 7166b0c1dd7abe00020c8ca235b7412687a594d1..a8590116b1ac72c3ee2508b1d89b3da09cd437f6 100644 --- a/rtree-c/test/expected/structfn/reduction/r010000.c +++ b/rtree-c/test/expected/structfn/reduction/r010000.c @@ -1,16 +1,13 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 do without param at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; -void fn(struct S0 a) -{ -} int main() { - fn(g0); + struct S0 g0 = { }; + g0; } diff --git a/rtree-c/test/expected/structfn/reduction/r010000.c.hs b/rtree-c/test/expected/structfn/reduction/r010000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r010000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010001.c b/rtree-c/test/expected/structfn/reduction/r010001.c index cfe3a5ebacc751ec5989fba85c552728a000ab8b..d7aedfc989b56ec5f6b370b6933cce95efe01597 100644 --- a/rtree-c/test/expected/structfn/reduction/r010001.c +++ b/rtree-c/test/expected/structfn/reduction/r010001.c @@ -1,15 +1,13 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 do without param at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; -void fn(struct S0 a) -{ -} int main() { + struct S0 g0 = { }; + 0; } diff --git a/rtree-c/test/expected/structfn/reduction/r010001.c.hs b/rtree-c/test/expected/structfn/reduction/r010001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r010001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00011.c b/rtree-c/test/expected/structfn/reduction/r01001.c similarity index 90% rename from rtree-c/test/expected/structfn/reduction/r00011.c rename to rtree-c/test/expected/structfn/reduction/r01001.c index 63d972b3090b3130d17c3b9491630462fcaa404d..93f2d60be0315f91f90ae11389b923bef8133dab 100644 --- a/rtree-c/test/expected/structfn/reduction/r00011.c +++ b/rtree-c/test/expected/structfn/reduction/r01001.c @@ -1,11 +1,11 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0 = { }; int main() { + struct S0 g0 = { }; } diff --git a/rtree-c/test/expected/structfn/reduction/r01001.c.hs b/rtree-c/test/expected/structfn/reduction/r01001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r01001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00110.c b/rtree-c/test/expected/structfn/reduction/r01010.c similarity index 96% rename from rtree-c/test/expected/structfn/reduction/r00110.c rename to rtree-c/test/expected/structfn/reduction/r01010.c index e3294f9fd5d30d10e1dd8fe13b3b9d03f0900b8d..a0d46e5c0aac2f7e5ec9cd1494ac5e2c30f6e182 100644 --- a/rtree-c/test/expected/structfn/reduction/r00110.c +++ b/rtree-c/test/expected/structfn/reduction/r01010.c @@ -1,8 +1,8 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r01010.c.hs b/rtree-c/test/expected/structfn/reduction/r01010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r01010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r101011.c b/rtree-c/test/expected/structfn/reduction/r010110.c similarity index 81% rename from rtree-c/test/expected/structfn/reduction/r101011.c rename to rtree-c/test/expected/structfn/reduction/r010110.c index d2e4883b144975b4c23d038c4f3765d880e2b558..c4efcd3222bd681aec7114b652cf42f94497bb2d 100644 --- a/rtree-c/test/expected/structfn/reduction/r101011.c +++ b/rtree-c/test/expected/structfn/reduction/r010110.c @@ -1,9 +1,9 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r010110.c.hs b/rtree-c/test/expected/structfn/reduction/r010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r010110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r00111.c b/rtree-c/test/expected/structfn/reduction/r010111.c similarity index 81% rename from rtree-c/test/expected/structfn/reduction/r00111.c rename to rtree-c/test/expected/structfn/reduction/r010111.c index 4c065ac51d32cefb9a8aef8a4a8ad5d076f4a62d..9fcc6cb37032733f27bde3c1b65ad214c33ac000 100644 --- a/rtree-c/test/expected/structfn/reduction/r00111.c +++ b/rtree-c/test/expected/structfn/reduction/r010111.c @@ -1,8 +1,9 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r010111.c.hs b/rtree-c/test/expected/structfn/reduction/r010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r010111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010100.c b/rtree-c/test/expected/structfn/reduction/r011000.c similarity index 79% rename from rtree-c/test/expected/structfn/reduction/r010100.c rename to rtree-c/test/expected/structfn/reduction/r011000.c index bc7df3bddb62124f1de0c2b0c31bddf0cc3bc57b..d0b2d9a3f3a12b65c2f46f73779aa06b2d45973b 100644 --- a/rtree-c/test/expected/structfn/reduction/r010100.c +++ b/rtree-c/test/expected/structfn/reduction/r011000.c @@ -1,13 +1,13 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 0 do without param at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 do without param at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; int main() { + struct S0 g0; g0; } diff --git a/rtree-c/test/expected/structfn/reduction/r011000.c.hs b/rtree-c/test/expected/structfn/reduction/r011000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r011000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r010101.c b/rtree-c/test/expected/structfn/reduction/r011001.c similarity index 79% rename from rtree-c/test/expected/structfn/reduction/r010101.c rename to rtree-c/test/expected/structfn/reduction/r011001.c index 7013526f594f0ad4813709320fd1fbf313ed572a..4433b1b7e0931c5c9ef02d0c1566f2f7ae2efaa5 100644 --- a/rtree-c/test/expected/structfn/reduction/r010101.c +++ b/rtree-c/test/expected/structfn/reduction/r011001.c @@ -1,13 +1,13 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 1 do without param at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 do without param at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; int main() { + struct S0 g0; 0; } diff --git a/rtree-c/test/expected/structfn/reduction/r011001.c.hs b/rtree-c/test/expected/structfn/reduction/r011001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r011001.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r01011.c b/rtree-c/test/expected/structfn/reduction/r01101.c similarity index 92% rename from rtree-c/test/expected/structfn/reduction/r01011.c rename to rtree-c/test/expected/structfn/reduction/r01101.c index 5b5160982696018155135df56ba6dc172655a608..740041aae94fcdc196117c56c62f6f43e64ed954 100644 --- a/rtree-c/test/expected/structfn/reduction/r01011.c +++ b/rtree-c/test/expected/structfn/reduction/r01101.c @@ -1,11 +1,11 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 0 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; -struct S0 g0; int main() { + struct S0 g0; } diff --git a/rtree-c/test/expected/structfn/reduction/r01101.c.hs b/rtree-c/test/expected/structfn/reduction/r01101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r01101.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r01110.c b/rtree-c/test/expected/structfn/reduction/r01110.c index 0ac93a535d6c86b5e97748e71046613fef63c35e..bb206e75fea7f8facac5f16f342ee1e138f2e1e8 100644 --- a/rtree-c/test/expected/structfn/reduction/r01110.c +++ b/rtree-c/test/expected/structfn/reduction/r01110.c @@ -1,8 +1,8 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r01110.c.hs b/rtree-c/test/expected/structfn/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r01110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r111011.c b/rtree-c/test/expected/structfn/reduction/r011110.c similarity index 81% rename from rtree-c/test/expected/structfn/reduction/r111011.c rename to rtree-c/test/expected/structfn/reduction/r011110.c index 2563e60be2ea52f9a0923c733754d2ea9c0c12cb..68a0fc5208d29a56d61a809c3fc2e77e4f5219ca 100644 --- a/rtree-c/test/expected/structfn/reduction/r111011.c +++ b/rtree-c/test/expected/structfn/reduction/r011110.c @@ -1,9 +1,9 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove declaration at ("test/cases/small/structfn.c": line 1) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r011110.c.hs b/rtree-c/test/expected/structfn/reduction/r011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r011110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r01111.c b/rtree-c/test/expected/structfn/reduction/r011111.c similarity index 81% rename from rtree-c/test/expected/structfn/reduction/r01111.c rename to rtree-c/test/expected/structfn/reduction/r011111.c index 59dd3775f493602f85e30daeee33d318f3248007..5a23fd1d0fa694712765c61a1c5af403f8cc5742 100644 --- a/rtree-c/test/expected/structfn/reduction/r01111.c +++ b/rtree-c/test/expected/structfn/reduction/r011111.c @@ -1,8 +1,9 @@ // 0 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove initializer at ("test/cases/small/structfn.c": line 4) +// 1 remove variable g0 at ("test/cases/small/structfn.c": line 4) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) struct S0 { }; int main() diff --git a/rtree-c/test/expected/structfn/reduction/r011111.c.hs b/rtree-c/test/expected/structfn/reduction/r011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r011111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r110010.c b/rtree-c/test/expected/structfn/reduction/r1000.c similarity index 51% rename from rtree-c/test/expected/structfn/reduction/r110010.c rename to rtree-c/test/expected/structfn/reduction/r1000.c index 8b5cf2deb4d76b39be3b8ed2872b470263e61410..3c6bd3274c6e8bc8c3be37db9f448ad3f21d56a5 100644 --- a/rtree-c/test/expected/structfn/reduction/r110010.c +++ b/rtree-c/test/expected/structfn/reduction/r1000.c @@ -1,11 +1,8 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0; void fn() { } diff --git a/rtree-c/test/expected/structfn/reduction/r1000.c.hs b/rtree-c/test/expected/structfn/reduction/r1000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r1000.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r100011.c b/rtree-c/test/expected/structfn/reduction/r100011.c deleted file mode 100644 index 35b3aba4ec7c31bdd16b9ffffe00d841123d38e1..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r100011.c +++ /dev/null @@ -1,14 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) - -struct S0 { } g0 = { }; -void fn() -{ -} -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/reduction/r110011.c b/rtree-c/test/expected/structfn/reduction/r10010.c similarity index 50% rename from rtree-c/test/expected/structfn/reduction/r110011.c rename to rtree-c/test/expected/structfn/reduction/r10010.c index 53c8c35ad0ba63e0d17414cf34b2df3ec5587fbc..5768756df4a2f860b6db2259f53bcddaecbc2a58 100644 --- a/rtree-c/test/expected/structfn/reduction/r110011.c +++ b/rtree-c/test/expected/structfn/reduction/r10010.c @@ -1,11 +1,9 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) -struct S0 { } g0; void fn() { } diff --git a/rtree-c/test/expected/structfn/reduction/r10010.c.hs b/rtree-c/test/expected/structfn/reduction/r10010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r100100.c b/rtree-c/test/expected/structfn/reduction/r100100.c deleted file mode 100644 index d63281f71af8b4a4dbd6ebe3d0549c1f9d7942cb..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r100100.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 0 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { } g0 = { }; -int main() -{ - g0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r100101.c b/rtree-c/test/expected/structfn/reduction/r100101.c deleted file mode 100644 index 3d361d9f01f36661d1488a2b00341899063aac7e..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r100101.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 1 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { } g0 = { }; -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r10011.c b/rtree-c/test/expected/structfn/reduction/r10011.c index d306c4429ede2de750ade279a6b876c3f79fe33a..9930cbc96731a54e9033997ecd5c427e355b0e32 100644 --- a/rtree-c/test/expected/structfn/reduction/r10011.c +++ b/rtree-c/test/expected/structfn/reduction/r10011.c @@ -1,10 +1,12 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) -struct S0 { } g0 = { }; +void fn() +{ +} int main() { } diff --git a/rtree-c/test/expected/structfn/reduction/r10011.c.hs b/rtree-c/test/expected/structfn/reduction/r10011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10011.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r100010.c b/rtree-c/test/expected/structfn/reduction/r1010.c similarity index 50% rename from rtree-c/test/expected/structfn/reduction/r100010.c rename to rtree-c/test/expected/structfn/reduction/r1010.c index d56d15d4f951f47240e371b501c79e63dfd8a44f..9c301d224404b02bbc20324b6e2c5a02ed48337e 100644 --- a/rtree-c/test/expected/structfn/reduction/r100010.c +++ b/rtree-c/test/expected/structfn/reduction/r1010.c @@ -1,11 +1,8 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) -struct S0 { } g0 = { }; void fn() { } diff --git a/rtree-c/test/expected/structfn/reduction/r1010.c.hs b/rtree-c/test/expected/structfn/reduction/r1010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r1010.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r101010.c b/rtree-c/test/expected/structfn/reduction/r101010.c deleted file mode 100644 index b1a23468d66792d6fa6873523fa27105baa81291..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r101010.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) - -struct S0 { }; -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r10110.c b/rtree-c/test/expected/structfn/reduction/r10110.c new file mode 100644 index 0000000000000000000000000000000000000000..5570993331b2e3be2619194a2199a88249074ab3 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10110.c @@ -0,0 +1,12 @@ +// 1 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) + +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r10110.c.hs b/rtree-c/test/expected/structfn/reduction/r10110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r101100.c b/rtree-c/test/expected/structfn/reduction/r101100.c deleted file mode 100644 index 112b943580f5e011548ef30a1b862155e754efa1..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r101100.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) - -void fn(struct S0 { } a) -{ -} -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/reduction/r1011010.c b/rtree-c/test/expected/structfn/reduction/r1011010.c deleted file mode 100644 index ea713d6e5eea384e35162a9106d7627b5990d7e1..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r1011010.c +++ /dev/null @@ -1,15 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) - -void fn() -{ -} -int main() -{ - fn(); -} diff --git a/rtree-c/test/expected/structfn/reduction/r1011011.c b/rtree-c/test/expected/structfn/reduction/r1011011.c deleted file mode 100644 index ef207a07835c996736199cd264b66c2eae60fffd..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r1011011.c +++ /dev/null @@ -1,14 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) - -void fn() -{ -} -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/reduction/r10111.c b/rtree-c/test/expected/structfn/reduction/r10111.c new file mode 100644 index 0000000000000000000000000000000000000000..93c9c08c5830f5aa7009a4dc061804c5b0e675b9 --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10111.c @@ -0,0 +1,12 @@ +// 1 remove declaration at ("test/cases/small/structfn.c": line 1) +// 0 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) + +void fn() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/structfn/reduction/r10111.c.hs b/rtree-c/test/expected/structfn/reduction/r10111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r10111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r101110.c b/rtree-c/test/expected/structfn/reduction/r101110.c deleted file mode 100644 index 6a5ae955b609d17db5449b92915e8cc000167f3d..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r101110.c +++ /dev/null @@ -1,11 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) - -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r111110.c b/rtree-c/test/expected/structfn/reduction/r110.c similarity index 51% rename from rtree-c/test/expected/structfn/reduction/r111110.c rename to rtree-c/test/expected/structfn/reduction/r110.c index 9c6f1ca91ce64976fbc4b6de4c4c5fe68994d8e0..471dc6ad7d620641fc035ab3285b085a5c7e916f 100644 --- a/rtree-c/test/expected/structfn/reduction/r111110.c +++ b/rtree-c/test/expected/structfn/reduction/r110.c @@ -1,9 +1,6 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 0 remove expr statement at ("test/cases/small/structfn.c": line 5) int main() { diff --git a/rtree-c/test/expected/structfn/reduction/r110.c.hs b/rtree-c/test/expected/structfn/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r110100.c b/rtree-c/test/expected/structfn/reduction/r110100.c deleted file mode 100644 index 94d8e202375e6050ccab22ef4c4c83797cbe46b4..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r110100.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 0 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { } g0; -int main() -{ - g0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r110101.c b/rtree-c/test/expected/structfn/reduction/r110101.c deleted file mode 100644 index 49570de9d5448e40326a1e3433f3b481c1ca9b10..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r110101.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) -// 1 do without param at ("test/cases/small/structfn.c": line 4) - -struct S0 { } g0; -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r11011.c b/rtree-c/test/expected/structfn/reduction/r1110.c similarity index 57% rename from rtree-c/test/expected/structfn/reduction/r11011.c rename to rtree-c/test/expected/structfn/reduction/r1110.c index 3b080030f8585578a0fcc447e04ecc3bd16118ea..43f4280e789b82f1e39de362587bdffc2a8861ef 100644 --- a/rtree-c/test/expected/structfn/reduction/r11011.c +++ b/rtree-c/test/expected/structfn/reduction/r1110.c @@ -1,10 +1,8 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 0 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 0 remove empty compound at ("test/cases/small/structfn.c": line 3) -struct S0 { } g0; int main() { } diff --git a/rtree-c/test/expected/structfn/reduction/r1110.c.hs b/rtree-c/test/expected/structfn/reduction/r1110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r1110.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r111010.c b/rtree-c/test/expected/structfn/reduction/r111010.c deleted file mode 100644 index 31270149cd72ad3e7d1a97731445cc71483c2527..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r111010.c +++ /dev/null @@ -1,12 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 0 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) - -struct S0 { }; -int main() -{ - 0; -} diff --git a/rtree-c/test/expected/structfn/reduction/r101111.c b/rtree-c/test/expected/structfn/reduction/r1111.c similarity index 50% rename from rtree-c/test/expected/structfn/reduction/r101111.c rename to rtree-c/test/expected/structfn/reduction/r1111.c index 517aa53dfb0c23761c88fabb34d01b3694049dee..9cfccf2a0c5127c0655e5d5bd664c477f449e504 100644 --- a/rtree-c/test/expected/structfn/reduction/r101111.c +++ b/rtree-c/test/expected/structfn/reduction/r1111.c @@ -1,9 +1,7 @@ // 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 0 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) +// 1 remove function fn at ("test/cases/small/structfn.c": line 2) +// 1 remove expr statement at ("test/cases/small/structfn.c": line 5) +// 1 remove empty compound at ("test/cases/small/structfn.c": line 3) int main() { diff --git a/rtree-c/test/expected/structfn/reduction/r1111.c.hs b/rtree-c/test/expected/structfn/reduction/r1111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..b208dcbf7ce2f4a6750332e5ed21eb1e0faa187c --- /dev/null +++ b/rtree-c/test/expected/structfn/reduction/r1111.c.hs @@ -0,0 +1,103 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) + ( Just [] ) [] () + ) () + ) + ] [] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "fn" 14182 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CSUType + ( CStruct CStructTag + ( Just + ( Ident "S0" 6227 () ) + ) Nothing [] () + ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "g0" 6247 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitList + ( CInitializerList [] ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CExpr + ( Just + ( CCall + ( CVar + ( Ident "fn" 14182 () ) () + ) + [ CVar + ( Ident "g0" 6247 () ) () + ] () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/structfn/reduction/r111100.c b/rtree-c/test/expected/structfn/reduction/r111100.c deleted file mode 100644 index 04b52402399dd7cb9004928fe751352748c1c79a..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r111100.c +++ /dev/null @@ -1,13 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 0 remove parameter at ("test/cases/small/structfn.c": line 3) - -void fn(struct S0 { } a) -{ -} -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/reduction/r1111010.c b/rtree-c/test/expected/structfn/reduction/r1111010.c deleted file mode 100644 index 26c61ac89818c34ac9cab72779302237d40e0f67..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r1111010.c +++ /dev/null @@ -1,15 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 0 remove expr statement at ("test/cases/small/structfn.c": line 4) - -void fn() -{ -} -int main() -{ - fn(); -} diff --git a/rtree-c/test/expected/structfn/reduction/r1111011.c b/rtree-c/test/expected/structfn/reduction/r1111011.c deleted file mode 100644 index f5d062084130a8b209e61fc8eb1b40ff06dac5a2..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r1111011.c +++ /dev/null @@ -1,14 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 0 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove parameter at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) - -void fn() -{ -} -int main() -{ -} diff --git a/rtree-c/test/expected/structfn/reduction/r111111.c b/rtree-c/test/expected/structfn/reduction/r111111.c deleted file mode 100644 index d2ccbfa4e1778795e8a81224ac0ced29d7b385e4..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/structfn/reduction/r111111.c +++ /dev/null @@ -1,10 +0,0 @@ -// 1 remove declaration at ("test/cases/small/structfn.c": line 1) -// 1 remove initializer at ("test/cases/small/structfn.c": line 2) -// 1 remove variable g0 at ("test/cases/small/structfn.c": line 2) -// 1 remove declaration at ("test/cases/small/structfn.c": line 2) -// 1 remove function fn at ("test/cases/small/structfn.c": line 3) -// 1 remove expr statement at ("test/cases/small/structfn.c": line 4) - -int main() -{ -} diff --git a/rtree-c/test/expected/typedef/reduction/r0000.c b/rtree-c/test/expected/typedef/reduction/r00000.c similarity index 83% rename from rtree-c/test/expected/typedef/reduction/r0000.c rename to rtree-c/test/expected/typedef/reduction/r00000.c index e5cb6776863b6825b797116275277846cba9028f..092f0c0fa8e358581415b02c582586eeebfef600 100644 --- a/rtree-c/test/expected/typedef/reduction/r0000.c +++ b/rtree-c/test/expected/typedef/reduction/r00000.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 0 inline variable x at ("test/cases/small/typedef.c": line 8) // 0 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r00000.c.hs b/rtree-c/test/expected/typedef/reduction/r00000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00000.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0001.c b/rtree-c/test/expected/typedef/reduction/r00001.c similarity index 83% rename from rtree-c/test/expected/typedef/reduction/r0001.c rename to rtree-c/test/expected/typedef/reduction/r00001.c index 0965039c30e7cce39e08e58b1c6ec65d3685fc9f..fb5d9b5be79c2cc2df1ffe04527314413a363f99 100644 --- a/rtree-c/test/expected/typedef/reduction/r0001.c +++ b/rtree-c/test/expected/typedef/reduction/r00001.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 0 inline variable x at ("test/cases/small/typedef.c": line 8) // 1 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r00001.c.hs b/rtree-c/test/expected/typedef/reduction/r00001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00001.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0010.c b/rtree-c/test/expected/typedef/reduction/r00010.c similarity index 82% rename from rtree-c/test/expected/typedef/reduction/r0010.c rename to rtree-c/test/expected/typedef/reduction/r00010.c index f6a29d2379749584f4b6ea584e350beee5813fe5..5f73d652212d9918d1e548393491bce50cd9c125 100644 --- a/rtree-c/test/expected/typedef/reduction/r0010.c +++ b/rtree-c/test/expected/typedef/reduction/r00010.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 1 inline variable x at ("test/cases/small/typedef.c": line 8) // 0 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r00010.c.hs b/rtree-c/test/expected/typedef/reduction/r00010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00010.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0011.c b/rtree-c/test/expected/typedef/reduction/r000110.c similarity index 70% rename from rtree-c/test/expected/typedef/reduction/r0011.c rename to rtree-c/test/expected/typedef/reduction/r000110.c index cee26a34db659ef6bb093191f1a1c089325a117a..98559cb6d94c9ad1149b5bbeae9186a3e942c7f6 100644 --- a/rtree-c/test/expected/typedef/reduction/r0011.c +++ b/rtree-c/test/expected/typedef/reduction/r000110.c @@ -1,7 +1,9 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 1 inline variable x at ("test/cases/small/typedef.c": line 8) // 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 7) typedef int uint64; void f(uint64 a) diff --git a/rtree-c/test/expected/typedef/reduction/r000110.c.hs b/rtree-c/test/expected/typedef/reduction/r000110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r000110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r000111.c b/rtree-c/test/expected/typedef/reduction/r000111.c new file mode 100644 index 0000000000000000000000000000000000000000..2e32ead39b96207e6b67aca99da5e0f1d91c9743 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r000111.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r000111.c.hs b/rtree-c/test/expected/typedef/reduction/r000111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r000111.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () 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 0000000000000000000000000000000000000000..231bd00fe3852f9b5f1eb2d063da6e5770dae583 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00100.c @@ -0,0 +1,15 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove return statement 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/r00100.c.hs b/rtree-c/test/expected/typedef/reduction/r00100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00100.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () 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 0000000000000000000000000000000000000000..3214e437e5d907e758cb21a9d875df7241f071b1 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00101.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ + uint64 x = 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r00101.c.hs b/rtree-c/test/expected/typedef/reduction/r00101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00101.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r00110.c b/rtree-c/test/expected/typedef/reduction/r00110.c new file mode 100644 index 0000000000000000000000000000000000000000..6c9eb8f0016434ca914b5e6c8c4153e868e284cb --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00110.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove return statement 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/r00110.c.hs b/rtree-c/test/expected/typedef/reduction/r00110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r00110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r001110.c b/rtree-c/test/expected/typedef/reduction/r001110.c new file mode 100644 index 0000000000000000000000000000000000000000..fd87f6b8ff65dd2046be5c8a590064594284631b --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r001110.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r001110.c.hs b/rtree-c/test/expected/typedef/reduction/r001110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r001110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r001111.c b/rtree-c/test/expected/typedef/reduction/r001111.c new file mode 100644 index 0000000000000000000000000000000000000000..6d59fc6f01a97f30001c40c8dd0b498fb881240c --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r001111.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 0 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f(uint64 a) +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r001111.c.hs b/rtree-c/test/expected/typedef/reduction/r001111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r001111.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0100.c b/rtree-c/test/expected/typedef/reduction/r01000.c similarity index 83% rename from rtree-c/test/expected/typedef/reduction/r0100.c rename to rtree-c/test/expected/typedef/reduction/r01000.c index 4cfd2ac02cf892a9d8fbd25628d23977af1dfb12..738f0ecc5ea07f5a5191aac1955f7fad521b1ff9 100644 --- a/rtree-c/test/expected/typedef/reduction/r0100.c +++ b/rtree-c/test/expected/typedef/reduction/r01000.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 0 inline variable x at ("test/cases/small/typedef.c": line 8) // 0 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r01000.c.hs b/rtree-c/test/expected/typedef/reduction/r01000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01000.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0101.c b/rtree-c/test/expected/typedef/reduction/r01001.c similarity index 82% rename from rtree-c/test/expected/typedef/reduction/r0101.c rename to rtree-c/test/expected/typedef/reduction/r01001.c index ea9c78343b75c38575bdcc9101a2b319e2cf1f7a..7bce9f648c165956210989c5c686dadcfcd7030a 100644 --- a/rtree-c/test/expected/typedef/reduction/r0101.c +++ b/rtree-c/test/expected/typedef/reduction/r01001.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 0 inline variable x at ("test/cases/small/typedef.c": line 8) // 1 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r01001.c.hs b/rtree-c/test/expected/typedef/reduction/r01001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01001.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0110.c b/rtree-c/test/expected/typedef/reduction/r01010.c similarity index 82% rename from rtree-c/test/expected/typedef/reduction/r0110.c rename to rtree-c/test/expected/typedef/reduction/r01010.c index e54fbe741c19fb61300c6a7d0657148a7ecc85b1..f68c94e17d96dbb4e8c9d3cc49f08835b84b17f1 100644 --- a/rtree-c/test/expected/typedef/reduction/r0110.c +++ b/rtree-c/test/expected/typedef/reduction/r01010.c @@ -1,5 +1,6 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 1 inline variable x at ("test/cases/small/typedef.c": line 8) // 0 remove return statement at ("test/cases/small/typedef.c": line 9) diff --git a/rtree-c/test/expected/typedef/reduction/r01010.c.hs b/rtree-c/test/expected/typedef/reduction/r01010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01010.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r0111.c b/rtree-c/test/expected/typedef/reduction/r010110.c similarity index 69% rename from rtree-c/test/expected/typedef/reduction/r0111.c rename to rtree-c/test/expected/typedef/reduction/r010110.c index 5a69909a2a0a20f9ede674ad28b99570035c299b..68b93d10010c2e937fbc19cb4289a87753dce44d 100644 --- a/rtree-c/test/expected/typedef/reduction/r0111.c +++ b/rtree-c/test/expected/typedef/reduction/r010110.c @@ -1,7 +1,9 @@ // 0 remove function f at ("test/cases/small/typedef.c": line 4) // 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) // 1 inline variable x at ("test/cases/small/typedef.c": line 8) // 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 7) typedef int uint64; void f() diff --git a/rtree-c/test/expected/typedef/reduction/r010110.c.hs b/rtree-c/test/expected/typedef/reduction/r010110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r010110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r010111.c b/rtree-c/test/expected/typedef/reduction/r010111.c new file mode 100644 index 0000000000000000000000000000000000000000..12edac8021b4e2d1b53126d5cb245c91c4f862a9 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r010111.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r010111.c.hs b/rtree-c/test/expected/typedef/reduction/r010111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r010111.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () 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 0000000000000000000000000000000000000000..be3236c7f15ccadb35e722ee3e1d78ee4c2995b0 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01100.c @@ -0,0 +1,15 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove return statement at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f() +{ +} +int main() +{ + uint64 x = 1; + return x; +} diff --git a/rtree-c/test/expected/typedef/reduction/r01100.c.hs b/rtree-c/test/expected/typedef/reduction/r01100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01100.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () 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 0000000000000000000000000000000000000000..ffddec56a5fa9900afa9c0a18f0c5797b84d77f6 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01101.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 0 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f() +{ +} +int main() +{ + uint64 x = 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r01101.c.hs b/rtree-c/test/expected/typedef/reduction/r01101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01101.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r01110.c b/rtree-c/test/expected/typedef/reduction/r01110.c new file mode 100644 index 0000000000000000000000000000000000000000..c07bc6604ac314d661695cbc58f90a891f250ba8 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01110.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 0 remove return statement at ("test/cases/small/typedef.c": line 9) + +typedef int uint64; +void f() +{ +} +int main() +{ + return 1; +} diff --git a/rtree-c/test/expected/typedef/reduction/r01110.c.hs b/rtree-c/test/expected/typedef/reduction/r01110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r01110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r011110.c b/rtree-c/test/expected/typedef/reduction/r011110.c new file mode 100644 index 0000000000000000000000000000000000000000..29233a1c479591fba683bd55e0f8345c0f0213b3 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r011110.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r011110.c.hs b/rtree-c/test/expected/typedef/reduction/r011110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r011110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r011111.c b/rtree-c/test/expected/typedef/reduction/r011111.c new file mode 100644 index 0000000000000000000000000000000000000000..f7fb80565313353c470ba037368981b48304abc4 --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r011111.c @@ -0,0 +1,14 @@ +// 0 remove function f at ("test/cases/small/typedef.c": line 4) +// 1 remove parameter at ("test/cases/small/typedef.c": line 4) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 4) +// 1 inline variable x at ("test/cases/small/typedef.c": line 8) +// 1 remove return statement at ("test/cases/small/typedef.c": line 9) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +void f() +{ +} +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r011111.c.hs b/rtree-c/test/expected/typedef/reduction/r011111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r011111.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r100.c.hs b/rtree-c/test/expected/typedef/reduction/r100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r100.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r101.c.hs b/rtree-c/test/expected/typedef/reduction/r101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r101.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r110.c.hs b/rtree-c/test/expected/typedef/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r111.c b/rtree-c/test/expected/typedef/reduction/r1110.c similarity index 77% rename from rtree-c/test/expected/typedef/reduction/r111.c rename to rtree-c/test/expected/typedef/reduction/r1110.c index 89442c79c185e4acb6df5d54c3ac85de7cc6d03d..8c8eedc42bdf7128988af37c9f4ba95161f4eacc 100644 --- a/rtree-c/test/expected/typedef/reduction/r111.c +++ b/rtree-c/test/expected/typedef/reduction/r1110.c @@ -1,6 +1,7 @@ // 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 return statement at ("test/cases/small/typedef.c": line 9) +// 0 remove empty compound at ("test/cases/small/typedef.c": line 7) typedef int uint64; int main() diff --git a/rtree-c/test/expected/typedef/reduction/r1110.c.hs b/rtree-c/test/expected/typedef/reduction/r1110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r1110.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/typedef/reduction/r1111.c b/rtree-c/test/expected/typedef/reduction/r1111.c new file mode 100644 index 0000000000000000000000000000000000000000..7ae8e89d6d690250b0d860abcda6b35a66cec44d --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r1111.c @@ -0,0 +1,9 @@ +// 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 return statement at ("test/cases/small/typedef.c": line 9) +// 1 remove empty compound at ("test/cases/small/typedef.c": line 7) + +typedef int uint64; +int main() +{ +} diff --git a/rtree-c/test/expected/typedef/reduction/r1111.c.hs b/rtree-c/test/expected/typedef/reduction/r1111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..8d49dd68aedcbaf9d8c3aa284831849b741c7aab --- /dev/null +++ b/rtree-c/test/expected/typedef/reduction/r1111.c.hs @@ -0,0 +1,94 @@ +CTranslUnit + [ CDeclExt + ( CDecl + [ CStorageSpec + ( CTypedef () ) + , CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "uint64" 245092139 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CVoidType () ) + ] + ( CDeclr + ( Just + ( Ident "f" 102 () ) + ) + [ CFunDeclr + ( CFunParamsNew + [ CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "a" 97 () ) + ) [] Nothing [] () + ) Nothing Nothing + ] () + ] False + ) [] () + ] Nothing [] () + ) [] + ( CCompound [] [] () ) () + ) + , CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CTypeDef + ( Ident "uint64" 245092139 () ) () + ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "x" 120 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 1 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CReturn + ( Just + ( CVar + ( Ident "x" 120 () ) () + ) + ) () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0000.c.hs b/rtree-c/test/expected/while-loops/reduction/r0000.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0000.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0001.c.hs b/rtree-c/test/expected/while-loops/reduction/r0001.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0001.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0010.c.hs b/rtree-c/test/expected/while-loops/reduction/r0010.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0010.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0011.c.hs b/rtree-c/test/expected/while-loops/reduction/r0011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0011.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0100.c b/rtree-c/test/expected/while-loops/reduction/r0100.c new file mode 100644 index 0000000000000000000000000000000000000000..416317d62b5a92cf256a81c502c71c4bf01c11f9 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0100.c @@ -0,0 +1,12 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove expr statement at ("test/cases/small/while-loops.c": line 4) +// 0 remove empty compound at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + int i = 0; + while (i < 10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0100.c.hs b/rtree-c/test/expected/while-loops/reduction/r0100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0100.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r0101.c b/rtree-c/test/expected/while-loops/reduction/r0101.c new file mode 100644 index 0000000000000000000000000000000000000000..e501a6cbe5ff4cf285ca63ebfd7b1e53fbbb76c5 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0101.c @@ -0,0 +1,12 @@ +// 0 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove expr statement at ("test/cases/small/while-loops.c": line 4) +// 0 remove empty compound at ("test/cases/small/while-loops.c": line 3) +// 1 replace by zero at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + int i = 0; + while (0) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r0101.c.hs b/rtree-c/test/expected/while-loops/reduction/r0101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r0101.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r01.c b/rtree-c/test/expected/while-loops/reduction/r011.c similarity index 70% rename from rtree-c/test/expected/while-loops/reduction/r01.c rename to rtree-c/test/expected/while-loops/reduction/r011.c index 7b9e05d7dcca7d838ab1831a166ade26cf37a937..cab76edd86cd627a8373e78accc939571412a250 100644 --- a/rtree-c/test/expected/while-loops/reduction/r01.c +++ b/rtree-c/test/expected/while-loops/reduction/r011.c @@ -1,5 +1,6 @@ // 0 inline variable i at ("test/cases/small/while-loops.c": line 2) // 1 remove expr statement at ("test/cases/small/while-loops.c": line 4) +// 1 remove empty compound at ("test/cases/small/while-loops.c": line 3) int main() { diff --git a/rtree-c/test/expected/while-loops/reduction/r011.c.hs b/rtree-c/test/expected/while-loops/reduction/r011.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r011.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r1.c b/rtree-c/test/expected/while-loops/reduction/r1.c deleted file mode 100644 index f34ba2b710ba3db9aa4d1efee256f46a4894a662..0000000000000000000000000000000000000000 --- a/rtree-c/test/expected/while-loops/reduction/r1.c +++ /dev/null @@ -1,5 +0,0 @@ -// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) - -int main() -{ -} diff --git a/rtree-c/test/expected/while-loops/reduction/r100.c b/rtree-c/test/expected/while-loops/reduction/r100.c new file mode 100644 index 0000000000000000000000000000000000000000..1351a25c083db2332de457a79934f49b57f42cb5 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r100.c @@ -0,0 +1,10 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove empty compound at ("test/cases/small/while-loops.c": line 3) +// 0 replace by zero at ("test/cases/small/while-loops.c": line 3) + +int main() +{ + while (0 < 10) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r100.c.hs b/rtree-c/test/expected/while-loops/reduction/r100.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r100.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r101.c b/rtree-c/test/expected/while-loops/reduction/r101.c new file mode 100644 index 0000000000000000000000000000000000000000..5afe597370c53bdde12ab9d8d86dbf1df2430c40 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r101.c @@ -0,0 +1,10 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 0 remove empty compound 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) + { + } +} diff --git a/rtree-c/test/expected/while-loops/reduction/r101.c.hs b/rtree-c/test/expected/while-loops/reduction/r101.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r101.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r110.c b/rtree-c/test/expected/while-loops/reduction/r110.c new file mode 100644 index 0000000000000000000000000000000000000000..7c5f9967c803ae1522f839f8cf8a80e53e30b010 --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r110.c @@ -0,0 +1,7 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove empty compound at ("test/cases/small/while-loops.c": line 3) +// 0 remove empty compound at ("test/cases/small/while-loops.c": line 1) + +int main() +{ +} diff --git a/rtree-c/test/expected/while-loops/reduction/r110.c.hs b/rtree-c/test/expected/while-loops/reduction/r110.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r110.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/expected/while-loops/reduction/r111.c b/rtree-c/test/expected/while-loops/reduction/r111.c new file mode 100644 index 0000000000000000000000000000000000000000..afa6daf99b2c4470c7182e9b1bd3e3bd881e6dec --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r111.c @@ -0,0 +1,7 @@ +// 1 inline variable i at ("test/cases/small/while-loops.c": line 2) +// 1 remove empty compound at ("test/cases/small/while-loops.c": line 3) +// 1 remove empty compound at ("test/cases/small/while-loops.c": line 1) + +int main() +{ +} diff --git a/rtree-c/test/expected/while-loops/reduction/r111.c.hs b/rtree-c/test/expected/while-loops/reduction/r111.c.hs new file mode 100644 index 0000000000000000000000000000000000000000..a2acb51373c0dbe97871302e7546c976e532e13d --- /dev/null +++ b/rtree-c/test/expected/while-loops/reduction/r111.c.hs @@ -0,0 +1,63 @@ +CTranslUnit + [ CFDefExt + ( CFunDef + [ CTypeSpec + ( CIntType () ) + ] + ( CDeclr + ( Just + ( Ident "main" 232419565 () ) + ) + [ CFunDeclr + ( CFunParamsNew [] False ) [] () + ] Nothing [] () + ) [] + ( CCompound [] + [ CBlockDecl + ( CDecl + [ CTypeSpec + ( CIntType () ) + ] + [ CDeclarationItem + ( CDeclr + ( Just + ( Ident "i" 105 () ) + ) [] Nothing [] () + ) + ( Just + ( CInitExpr + ( CConst + ( CIntConst 0 () ) + ) () + ) + ) Nothing + ] () + ) + , CBlockStmt + ( CWhile + ( CBinary CLeOp + ( CVar + ( Ident "i" 105 () ) () + ) + ( CConst + ( CIntConst 10 () ) + ) () + ) + ( CCompound [] + [ CBlockStmt + ( CExpr + ( Just + ( CUnary CPostIncOp + ( CVar + ( Ident "i" 105 () ) () + ) () + ) + ) () + ) + ] () + ) False () + ) + ] () + ) () + ) + ] () diff --git a/rtree-c/test/src/ReduceCSpec.hs b/rtree-c/test/src/ReduceCSpec.hs index f2a221e98867dcedf3b6cf8b730335c995a11d68..6ae8593324b4e26efad80ae4bbb9221526648457 100644 --- a/rtree-c/test/src/ReduceCSpec.hs +++ b/rtree-c/test/src/ReduceCSpec.hs @@ -30,11 +30,13 @@ import Data.String import qualified Language.C.System.GCC as C import ReduceC import System.Directory.Internal.Prelude (tryIOError) +import System.IO import System.Process.Typed +import Text.Pretty.Simple spec :: Spec spec = do - specSmallCases + focus $ specSmallCases specLargeCases specLargeCases :: Spec @@ -115,15 +117,17 @@ specSmallCases = do forM_ (RTree.iinputs (defaultReduceC c)) \(i, _) -> do let rfile = expected </> "reduction" </> "r" <> debugShow i <.> "c" renderWithChoices rfile (IRTree.probe (defaultReduceC c) i) + withFile (rfile <.> "hs") WriteMode \h -> + pHPrint h (c $> ()) ) - do - it "should validate all reductions" $ \a -> do - when (takeExtension a == ".c") do - validate a + do + it "should validate all reductions" $ \a -> do + when (takeExtension a == ".c") do + validate a validate :: FilePath -> IO () validate fp = do - (ec, _, stderr) <- readProcess (proc "clang" ["-o", "/dev/null", fp]) + (ec, _, stderr_) <- readProcess (proc "clang" ["-o", "/dev/null", fp]) case ec of ExitFailure _ -> expectationFailure $ @@ -134,7 +138,7 @@ validate fp = do . LazyText.unlines . filter (LazyText.isInfixOf "error") . LazyText.lines - $ LazyText.decodeUtf8 stderr + $ LazyText.decodeUtf8 stderr_ ) ExitSuccess -> pure ()