diff --git a/rtree-c/src/ReduceC.hs b/rtree-c/src/ReduceC.hs
index 59c991968c2f99dc93c04f48460eabfceb16c907..a94ca0b01bedb6fe911cba990bd425a9342a4dbb 100644
--- a/rtree-c/src/ReduceC.hs
+++ b/rtree-c/src/ReduceC.hs
@@ -165,35 +165,41 @@ reduceCExternalDeclaration r ctx = case r of
         pure (Just $ C.CFDefExt <$> reduceCFunDef fun ctx, ctx)
     | otherwise ->
         case functionName fun of
-          Just fid -> do
-            let nctx =
-                  ctx & foldr \case
-                    (Just t, Just i) -> addInlineExpr i (IEKeep t)
-                    (Nothing, Just i) -> addInlineExpr i IEDelete
-                    (_, Nothing) -> id
-            let red fun' ps = reduceCFunDef fun' (nctx ps)
-            case Map.lookup fid . inlineExprs $ ctx of
-              Just (IEKeep (CTFun args)) -> do
-                (fun', ps) <- reduceParamsTo args fun
-                pure
-                  ( Just (C.CFDefExt <$> red fun' ps)
-                  , addInlineExpr fid (IEKeep (CTFun (map fst ps))) ctx
-                  )
-              _ow -> do
-                split
-                  ("remove function " <> C.identToString fid, C.posOf r)
-                  (pure (Nothing, addInlineExpr fid IEDelete ctx))
-                  do
-                    (fun', ps) <- reduceParams ctx fun
+          Just fid
+            | shouldDeleteFunction ctx fun -> do
+                pure (Nothing, addInlineExpr fid IEDelete ctx)
+            | otherwise -> do
+                let nctx =
+                      ctx & foldr \case
+                        (Just t, Just i) -> addInlineExpr i (IEKeep t)
+                        (Nothing, Just i) -> addInlineExpr i IEDelete
+                        (_, Nothing) -> id
+                let red fun' ps = reduceCFunDef fun' (nctx ps)
+                case Map.lookup fid . inlineExprs $ ctx of
+                  Just (IEKeep (CTFun args)) -> do
+                    (fun', ps) <- reduceParamsTo args fun
                     pure
                       ( Just (C.CFDefExt <$> red fun' ps)
                       , addInlineExpr fid (IEKeep (CTFun (map fst ps))) ctx
                       )
-          Nothing ->
-            split
-              ("remove function", C.posOf r)
-              (pure (Nothing, ctx))
-              (pure (Just (C.CFDefExt <$> reduceCFunDef fun ctx), ctx))
+                  _ow -> do
+                    split
+                      ("remove function " <> C.identToString fid, C.posOf r)
+                      (pure (Nothing, addInlineExpr fid IEDelete ctx))
+                      do
+                        (fun', ps) <- reduceParams ctx fun
+                        pure
+                          ( Just (C.CFDefExt <$> red fun' ps)
+                          , addInlineExpr fid (IEKeep (CTFun (map fst ps))) ctx
+                          )
+          Nothing
+            | shouldDeleteFunction ctx fun -> do
+                pure (Nothing, ctx)
+            | otherwise -> do
+                split
+                  ("remove function", C.posOf r)
+                  (pure (Nothing, ctx))
+                  (pure (Just (C.CFDefExt <$> reduceCFunDef fun ctx), ctx))
   C.CDeclExt decl -> do
     (decl', ctx') <- handleDecl decl ctx
     case decl' of
@@ -600,21 +606,26 @@ reduceCStatement smt labs ctx = case smt of
   C.CFor e1 e2 e3 s ni -> do
     (me1', ctx') <- case e1 of
       C.CForDecl d@(C.CDecl rec decl ni') -> do
-        (decl', ctx') <- foldr (reduceCDeclarationItem (shouldDeleteDeclaration ctx d) (ctype ctx rec)) (pure ([], ctx)) decl
+        (decl', ctx') <-
+          foldr
+            (reduceCDeclarationItem (shouldDeleteDeclaration ctx d) (ctype ctx rec))
+            (pure ([], ctx))
+            decl
         res <-
           if null decl'
             then
-              whenSplit
-                (AllowEmptyDeclarations `isIn` ctx')
-                ("remove empty declaration", C.posOf ni')
-                (pure Nothing)
-                (pure $ Just $ C.CForDecl (C.CDecl rec decl' ni'))
+              if AllowEmptyDeclarations `isIn` ctx'
+                then
+                  split
+                    ("remove empty declaration", C.posOf ni')
+                    (pure Nothing)
+                    (pure $ Just $ C.CForDecl (C.CDecl rec decl' ni'))
+                else pure Nothing
             else pure $ Just $ C.CForDecl (C.CDecl rec decl' ni')
         pure (res, ctx')
       C.CForInitializing e -> do
         e' <- maybeSplit ("remove initializer", C.posOf ni) (e >>= \e' -> reduceCExpr e' ctx)
-        whenSplit
-          (AllowEmptyDeclarations `isIn` ctx)
+        split
           ("remove empty declaration", C.posOf ni)
           (pure (Nothing, ctx))
           (pure (Just $ C.CForInitializing e', ctx))
@@ -867,10 +878,14 @@ inlineTypeDefsCDeclaration decl ctx =
       C.CDecl (inlineTypeDefsSpecs items ctx) (map (`inlineTypeDefsCDI` ctx) decli) ni
     a -> don'tHandle a
 
+shouldDeleteFunction :: Context -> C.CFunctionDef C.NodeInfo -> Bool
+shouldDeleteFunction ctx (C.CFunDef spec _ _ _ _) =
+  any (shouldDeleteDeclSpec ctx) spec
+
 shouldDeleteDeclaration :: Context -> C.CDeclaration C.NodeInfo -> Bool
 shouldDeleteDeclaration ctx decl =
   case decl of
-    C.CDecl items decli _ -> any shouldDeleteDeclSpec items || any shouldDeleteDeclItem decli
+    C.CDecl items decli _ -> any (shouldDeleteDeclSpec ctx) items || any shouldDeleteDeclItem decli
     a -> don'tHandle a
  where
   shouldDeleteDeclItem = \case
@@ -887,15 +902,16 @@ shouldDeleteDeclaration ctx decl =
     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
+shouldDeleteDeclSpec :: Context -> C.CDeclarationSpecifier C.NodeInfo -> Bool
+shouldDeleteDeclSpec ctx = \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 =
diff --git a/rtree-c/test/expected/for/reduction/r000000.c b/rtree-c/test/expected/for/reduction/r0000000.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r000000.c
rename to rtree-c/test/expected/for/reduction/r0000000.c
index cb0ad0b245b6355aaedff69880c56450e821731b..16e5ccb0a52a2ec810a222415a288d463f4bba46 100644
--- a/rtree-c/test/expected/for/reduction/r000000.c
+++ b/rtree-c/test/expected/for/reduction/r0000000.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r000000.c.hs b/rtree-c/test/expected/for/reduction/r0000000.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r000000.c.hs
rename to rtree-c/test/expected/for/reduction/r0000000.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000001.c b/rtree-c/test/expected/for/reduction/r0000001.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r000001.c
rename to rtree-c/test/expected/for/reduction/r0000001.c
index 8300117b92351aa366539495ec1e20b744eec5bf..e6051323047c72abbd01eb8f70cf3674949eafe2 100644
--- a/rtree-c/test/expected/for/reduction/r000001.c
+++ b/rtree-c/test/expected/for/reduction/r0000001.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r000001.c.hs b/rtree-c/test/expected/for/reduction/r0000001.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r000001.c.hs
rename to rtree-c/test/expected/for/reduction/r0000001.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r00000100.c b/rtree-c/test/expected/for/reduction/r00000100.c
new file mode 100644
index 0000000000000000000000000000000000000000..d4ade4edff9556cd4b36cdb8b35b7619e3146285
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00000100.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r000010.c.hs b/rtree-c/test/expected/for/reduction/r00000100.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r000010.c.hs
rename to rtree-c/test/expected/for/reduction/r00000100.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000001010.c b/rtree-c/test/expected/for/reduction/r000001010.c
new file mode 100644
index 0000000000000000000000000000000000000000..0f15f2a06816df9db3d6b23ec807e514ea080693
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000001010.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r000011.c.hs b/rtree-c/test/expected/for/reduction/r000001010.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r000011.c.hs
rename to rtree-c/test/expected/for/reduction/r000001010.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000010110.c b/rtree-c/test/expected/for/reduction/r0000010110.c
new file mode 100644
index 0000000000000000000000000000000000000000..b55bf5a39ebc894184216149b1735a8cfc78d40a
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000010110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+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/r0000010110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r00010.c.hs
rename to rtree-c/test/expected/for/reduction/r0000010110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000010111.c b/rtree-c/test/expected/for/reduction/r0000010111.c
new file mode 100644
index 0000000000000000000000000000000000000000..3cc0f2b433846f7e5e8600be69fb4bc212e7363f
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000010111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r00011.c.hs b/rtree-c/test/expected/for/reduction/r0000010111.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r00011.c.hs
rename to rtree-c/test/expected/for/reduction/r0000010111.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r00000110.c b/rtree-c/test/expected/for/reduction/r00000110.c
new file mode 100644
index 0000000000000000000000000000000000000000..f2bde6b186d7c0e029fb98c57e2b6825d6597532
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00000110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0010.c.hs b/rtree-c/test/expected/for/reduction/r00000110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r0010.c.hs
rename to rtree-c/test/expected/for/reduction/r00000110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000001110.c b/rtree-c/test/expected/for/reduction/r000001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..e159471e5e4651089180759715f52f77ebb36c1e
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000001110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0011.c.hs b/rtree-c/test/expected/for/reduction/r000001110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r0011.c.hs
rename to rtree-c/test/expected/for/reduction/r000001110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000011110.c b/rtree-c/test/expected/for/reduction/r0000011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..93de9e9f2a27934aa57c4c12f4517966fdc81e8c
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000011110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010000.c.hs b/rtree-c/test/expected/for/reduction/r0000011110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r010000.c.hs
rename to rtree-c/test/expected/for/reduction/r0000011110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000011111.c b/rtree-c/test/expected/for/reduction/r0000011111.c
new file mode 100644
index 0000000000000000000000000000000000000000..7900a9666e6fc57c28dc13847e5adb16f583c941
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000011111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010001.c.hs b/rtree-c/test/expected/for/reduction/r0000011111.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r010001.c.hs
rename to rtree-c/test/expected/for/reduction/r0000011111.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000010.c b/rtree-c/test/expected/for/reduction/r0000100.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r000010.c
rename to rtree-c/test/expected/for/reduction/r0000100.c
index 958c7b6415d2fc8fdcd743f3b65f9f38ca043917..a16d8f384e91b1aa196c8d24785681cd46f9ded1 100644
--- a/rtree-c/test/expected/for/reduction/r000010.c
+++ b/rtree-c/test/expected/for/reduction/r0000100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r010010.c.hs b/rtree-c/test/expected/for/reduction/r0000100.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r010010.c.hs
rename to rtree-c/test/expected/for/reduction/r0000100.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000011.c b/rtree-c/test/expected/for/reduction/r0000101.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r000011.c
rename to rtree-c/test/expected/for/reduction/r0000101.c
index 3e1f08b117cc9a14d8dcfbec922193c2ab541abf..0d6c9fc04715a81309daf2a823d2ccf63f787968 100644
--- a/rtree-c/test/expected/for/reduction/r000011.c
+++ b/rtree-c/test/expected/for/reduction/r0000101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r010011.c.hs b/rtree-c/test/expected/for/reduction/r0000101.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r010011.c.hs
rename to rtree-c/test/expected/for/reduction/r0000101.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r00001100.c b/rtree-c/test/expected/for/reduction/r00001100.c
new file mode 100644
index 0000000000000000000000000000000000000000..4ee8e201be17a250735f5b20c1eadfd960717087
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00001100.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01010.c.hs b/rtree-c/test/expected/for/reduction/r00001100.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r01010.c.hs
rename to rtree-c/test/expected/for/reduction/r00001100.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000011010.c b/rtree-c/test/expected/for/reduction/r000011010.c
new file mode 100644
index 0000000000000000000000000000000000000000..452a5b287dae7eb8cebd294e2baaa037dd629d60
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000011010.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01011.c.hs b/rtree-c/test/expected/for/reduction/r000011010.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r01011.c.hs
rename to rtree-c/test/expected/for/reduction/r000011010.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000110110.c b/rtree-c/test/expected/for/reduction/r0000110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..5cb8f9b5defca29c68fabfc9e92b7e382b038f9c
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000110110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0110.c.hs b/rtree-c/test/expected/for/reduction/r0000110110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r0110.c.hs
rename to rtree-c/test/expected/for/reduction/r0000110110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000110111.c b/rtree-c/test/expected/for/reduction/r0000110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..8bf9c6932c0895ebe1f8f72578a7cd1fe3e9aa26
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000110111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0111.c.hs b/rtree-c/test/expected/for/reduction/r0000110111.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r0111.c.hs
rename to rtree-c/test/expected/for/reduction/r0000110111.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r00001110.c b/rtree-c/test/expected/for/reduction/r00001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..6a8dad7f0f3933596f7abba416cc34242c0868c1
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00001110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r10.c.hs b/rtree-c/test/expected/for/reduction/r00001110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r10.c.hs
rename to rtree-c/test/expected/for/reduction/r00001110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r000011110.c b/rtree-c/test/expected/for/reduction/r000011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..fc9cbc408b4694262de8c4f104d0329822fd993a
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000011110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r11.c.hs b/rtree-c/test/expected/for/reduction/r000011110.c.hs
similarity index 100%
rename from rtree-c/test/expected/for/reduction/r11.c.hs
rename to rtree-c/test/expected/for/reduction/r000011110.c.hs
diff --git a/rtree-c/test/expected/for/reduction/r0000111110.c b/rtree-c/test/expected/for/reduction/r0000111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..a1971e25299f46b6515732a133bb1ebbf148f74a
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000111110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0000111110.c.hs b/rtree-c/test/expected/for/reduction/r0000111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000111110.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/r0000111111.c b/rtree-c/test/expected/for/reduction/r0000111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..fc9547db521a19be18072578a6c90dab7d937bf5
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000111111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0000111111.c.hs b/rtree-c/test/expected/for/reduction/r0000111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0000111111.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/r00010.c b/rtree-c/test/expected/for/reduction/r000100.c
similarity index 84%
rename from rtree-c/test/expected/for/reduction/r00010.c
rename to rtree-c/test/expected/for/reduction/r000100.c
index a58f913c8a98eedceab57d425e6ad694359f2baa..7223f91adef79d9fb9ad3c28f353a8bfbfd65d9c 100644
--- a/rtree-c/test/expected/for/reduction/r00010.c
+++ b/rtree-c/test/expected/for/reduction/r000100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r000100.c.hs b/rtree-c/test/expected/for/reduction/r000100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000100.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/r000101.c
similarity index 84%
rename from rtree-c/test/expected/for/reduction/r00011.c
rename to rtree-c/test/expected/for/reduction/r000101.c
index b988cd7f1ff6d33b3f62cffae8a9ab8e864ce4d8..43936b0c2e2be4a691ee62c2190f733413d82724 100644
--- a/rtree-c/test/expected/for/reduction/r00011.c
+++ b/rtree-c/test/expected/for/reduction/r000101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r000101.c.hs b/rtree-c/test/expected/for/reduction/r000101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000101.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/r0001100.c b/rtree-c/test/expected/for/reduction/r0001100.c
new file mode 100644
index 0000000000000000000000000000000000000000..b560a1f3a1b8bd6d0c97fe1e5846693499cd3c6d
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0001100.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0001100.c.hs b/rtree-c/test/expected/for/reduction/r0001100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0001100.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/r00011010.c b/rtree-c/test/expected/for/reduction/r00011010.c
new file mode 100644
index 0000000000000000000000000000000000000000..d027c29fdd4cc06cfd50e5470c56986b47ee36f2
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00011010.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r00011010.c.hs b/rtree-c/test/expected/for/reduction/r00011010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00011010.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/r000110110.c b/rtree-c/test/expected/for/reduction/r000110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..6fb688055a8e5530c5af69d0fa84d003ddb81552
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000110110.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r000110110.c.hs b/rtree-c/test/expected/for/reduction/r000110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000110110.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/r000110111.c b/rtree-c/test/expected/for/reduction/r000110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..5f1d72a3d176817a09ea0cd37a35f077af569bf2
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000110111.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r000110111.c.hs b/rtree-c/test/expected/for/reduction/r000110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000110111.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/r0001110.c b/rtree-c/test/expected/for/reduction/r0001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..bdd972c9b0b3be11bd4c73f7b82dfe18b233207b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0001110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0001110.c.hs b/rtree-c/test/expected/for/reduction/r0001110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0001110.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/r00011110.c b/rtree-c/test/expected/for/reduction/r00011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..e061c6b29076a41a8809b390a4f9250fad09c042
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00011110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r00011110.c.hs b/rtree-c/test/expected/for/reduction/r00011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00011110.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/r000111110.c b/rtree-c/test/expected/for/reduction/r000111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..c7f2f8e13c8fbb292d673dc6e7e1e69298772adc
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000111110.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r000111110.c.hs b/rtree-c/test/expected/for/reduction/r000111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000111110.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/r000111111.c b/rtree-c/test/expected/for/reduction/r000111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..94ef7d8bb892ef53f07c56646142ea00162e829b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000111111.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r000111111.c.hs b/rtree-c/test/expected/for/reduction/r000111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r000111111.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/r0010.c b/rtree-c/test/expected/for/reduction/r00100.c
similarity index 81%
rename from rtree-c/test/expected/for/reduction/r0010.c
rename to rtree-c/test/expected/for/reduction/r00100.c
index d8181bf4703c8b5aec110fa2fbb8f8b5f64851a9..451267d31f51436c4f0920da5eb0b39616737ccc 100644
--- a/rtree-c/test/expected/for/reduction/r0010.c
+++ b/rtree-c/test/expected/for/reduction/r00100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r00100.c.hs b/rtree-c/test/expected/for/reduction/r00100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00100.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/r00101.c
similarity index 81%
rename from rtree-c/test/expected/for/reduction/r0011.c
rename to rtree-c/test/expected/for/reduction/r00101.c
index b96bfe1796097c69c62a0b703768194b2657ef16..fe25665b2fcc9793a49f357b09591cd5f8a9128c 100644
--- a/rtree-c/test/expected/for/reduction/r0011.c
+++ b/rtree-c/test/expected/for/reduction/r00101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 static int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r00101.c.hs b/rtree-c/test/expected/for/reduction/r00101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00101.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/r001100.c b/rtree-c/test/expected/for/reduction/r001100.c
new file mode 100644
index 0000000000000000000000000000000000000000..cdb1956f040ab0ca075459b320794b8c09cdb0b7
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r001100.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r001100.c.hs b/rtree-c/test/expected/for/reduction/r001100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r001100.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/r0011010.c b/rtree-c/test/expected/for/reduction/r0011010.c
new file mode 100644
index 0000000000000000000000000000000000000000..a8482e2fc7fde4ab3d126b8d7fe7e141ca45bdce
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0011010.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0011010.c.hs b/rtree-c/test/expected/for/reduction/r0011010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0011010.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/r00110110.c b/rtree-c/test/expected/for/reduction/r00110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..6f7f02a90e5ae43a321f9734568be1bf0376f5da
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00110110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r00110110.c.hs b/rtree-c/test/expected/for/reduction/r00110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00110110.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/r00110111.c b/rtree-c/test/expected/for/reduction/r00110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..4168cc5f73a6c8fa8cdfa0c0544380a014ee22d7
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00110111.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r00110111.c.hs b/rtree-c/test/expected/for/reduction/r00110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00110111.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/r001110.c b/rtree-c/test/expected/for/reduction/r001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..42779b3d21f2acb1b270e16245291aecba452bb5
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r001110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r001110.c.hs b/rtree-c/test/expected/for/reduction/r001110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r001110.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/r0011110.c b/rtree-c/test/expected/for/reduction/r0011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..427376d95eaf5c9c3fc650993d03112033049a3b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0011110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+static int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0011110.c.hs b/rtree-c/test/expected/for/reduction/r0011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0011110.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/r00111110.c b/rtree-c/test/expected/for/reduction/r00111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..a65f5a87290bb2cb04747c551aed3540cc473ad8
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00111110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r00111110.c.hs b/rtree-c/test/expected/for/reduction/r00111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00111110.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/r00111111.c b/rtree-c/test/expected/for/reduction/r00111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..2918b44cf074b898e234b32918ab7ff6fffcd861
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00111111.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+static int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r00111111.c.hs b/rtree-c/test/expected/for/reduction/r00111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r00111111.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/r010000.c b/rtree-c/test/expected/for/reduction/r0100000.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r010000.c
rename to rtree-c/test/expected/for/reduction/r0100000.c
index 5fe1c0b2d4263e3edc84bc700583ca5796c797e2..551a5c393d7a30f5d62edf02987ce80daf1a738f 100644
--- a/rtree-c/test/expected/for/reduction/r010000.c
+++ b/rtree-c/test/expected/for/reduction/r0100000.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r0100000.c.hs b/rtree-c/test/expected/for/reduction/r0100000.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100000.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/r0100001.c
similarity index 86%
rename from rtree-c/test/expected/for/reduction/r010001.c
rename to rtree-c/test/expected/for/reduction/r0100001.c
index 4236d05ee07e7dd6a899107fbf51256feec41be2..935910af28a9b80e23f639036bb600e49a584543 100644
--- a/rtree-c/test/expected/for/reduction/r010001.c
+++ b/rtree-c/test/expected/for/reduction/r0100001.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r0100001.c.hs b/rtree-c/test/expected/for/reduction/r0100001.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100001.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/r01000100.c b/rtree-c/test/expected/for/reduction/r01000100.c
new file mode 100644
index 0000000000000000000000000000000000000000..727cfb5418523ef83f4c2748c102aa5cbca4fe34
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01000100.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01000100.c.hs b/rtree-c/test/expected/for/reduction/r01000100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01000100.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/r010001010.c b/rtree-c/test/expected/for/reduction/r010001010.c
new file mode 100644
index 0000000000000000000000000000000000000000..00a3e8346b0f727f8d919183b4aa5c0726b7e535
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010001010.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r010001010.c.hs b/rtree-c/test/expected/for/reduction/r010001010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010001010.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/r0100010110.c b/rtree-c/test/expected/for/reduction/r0100010110.c
new file mode 100644
index 0000000000000000000000000000000000000000..33b57ca41cf5d8f585391ae4d72241a08820a1d2
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100010110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100010110.c.hs b/rtree-c/test/expected/for/reduction/r0100010110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100010110.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/r0100010111.c b/rtree-c/test/expected/for/reduction/r0100010111.c
new file mode 100644
index 0000000000000000000000000000000000000000..628e0a3ea7ff2bb94e790125dba96a4a55821eeb
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100010111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100010111.c.hs b/rtree-c/test/expected/for/reduction/r0100010111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100010111.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/r01000110.c b/rtree-c/test/expected/for/reduction/r01000110.c
new file mode 100644
index 0000000000000000000000000000000000000000..e8c9673bcdaa491e78dbaf689b498a5ea3ba1f40
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01000110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01000110.c.hs b/rtree-c/test/expected/for/reduction/r01000110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01000110.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/r010001110.c b/rtree-c/test/expected/for/reduction/r010001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..52ee14f55951c6e9d113c79d2288e5f929c1e959
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010001110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r010001110.c.hs b/rtree-c/test/expected/for/reduction/r010001110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010001110.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/r0100011110.c b/rtree-c/test/expected/for/reduction/r0100011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..f7303efa21636c93b7bee973a07ffbb18d24530a
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100011110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100011110.c.hs b/rtree-c/test/expected/for/reduction/r0100011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100011110.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/r0100011111.c b/rtree-c/test/expected/for/reduction/r0100011111.c
new file mode 100644
index 0000000000000000000000000000000000000000..7aa9cb018cb7108a1c216901044a6a08be2dd538
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100011111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100011111.c.hs b/rtree-c/test/expected/for/reduction/r0100011111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100011111.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/r010010.c b/rtree-c/test/expected/for/reduction/r0100100.c
similarity index 85%
rename from rtree-c/test/expected/for/reduction/r010010.c
rename to rtree-c/test/expected/for/reduction/r0100100.c
index 811a7a69a3d291b50530abd868f1a6e642b676b0..cd289b0d671150eec9b018f1f226bda5a66513d5 100644
--- a/rtree-c/test/expected/for/reduction/r010010.c
+++ b/rtree-c/test/expected/for/reduction/r0100100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r0100100.c.hs b/rtree-c/test/expected/for/reduction/r0100100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100100.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/r0100101.c
similarity index 85%
rename from rtree-c/test/expected/for/reduction/r010011.c
rename to rtree-c/test/expected/for/reduction/r0100101.c
index de101b4aa656c7d003570c6d2667b42b12349433..0d2dac9d453a312c54a5d03787c77786d7b20eb4 100644
--- a/rtree-c/test/expected/for/reduction/r010011.c
+++ b/rtree-c/test/expected/for/reduction/r0100101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r0100101.c.hs b/rtree-c/test/expected/for/reduction/r0100101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100101.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/r01001100.c b/rtree-c/test/expected/for/reduction/r01001100.c
new file mode 100644
index 0000000000000000000000000000000000000000..41bf8383af58305d617e0fde6d6fbdd05be65c36
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01001100.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01001100.c.hs b/rtree-c/test/expected/for/reduction/r01001100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01001100.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/r010011010.c b/rtree-c/test/expected/for/reduction/r010011010.c
new file mode 100644
index 0000000000000000000000000000000000000000..681bcbed6e5fe5b46c4e7aca0429844ac34f72bd
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010011010.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r010011010.c.hs b/rtree-c/test/expected/for/reduction/r010011010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010011010.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/r0100110110.c b/rtree-c/test/expected/for/reduction/r0100110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..b618c553fa756804e356ba7224fe181f64ea6015
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100110110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100110110.c.hs b/rtree-c/test/expected/for/reduction/r0100110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100110110.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/r0100110111.c b/rtree-c/test/expected/for/reduction/r0100110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..dee0ec6a9deaa6b1e12ca4e921e2c694ac0f8e7b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100110111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100110111.c.hs b/rtree-c/test/expected/for/reduction/r0100110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100110111.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/r01001110.c b/rtree-c/test/expected/for/reduction/r01001110.c
new file mode 100644
index 0000000000000000000000000000000000000000..d99057c9161033f36ea9c4b6c5b3ed8536a6a9e0
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01001110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01001110.c.hs b/rtree-c/test/expected/for/reduction/r01001110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01001110.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/r010011110.c b/rtree-c/test/expected/for/reduction/r010011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..ce65e14490032d425704934ca31fbb324e6b9db5
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010011110.c
@@ -0,0 +1,16 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r010011110.c.hs b/rtree-c/test/expected/for/reduction/r010011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010011110.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/r0100111110.c b/rtree-c/test/expected/for/reduction/r0100111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..c8f01a0239ecfcb3a52bc17d923a4c4c216a974b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100111110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100111110.c.hs b/rtree-c/test/expected/for/reduction/r0100111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100111110.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/r0100111111.c b/rtree-c/test/expected/for/reduction/r0100111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..b487967ceee795813927ca3589a835ee9ec2f5c5
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100111111.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r0100111111.c.hs b/rtree-c/test/expected/for/reduction/r0100111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0100111111.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/r01010.c b/rtree-c/test/expected/for/reduction/r010100.c
similarity index 83%
rename from rtree-c/test/expected/for/reduction/r01010.c
rename to rtree-c/test/expected/for/reduction/r010100.c
index d0e4bbf5cedf2e92261213bb755cc73317b1a699..ac032d7c3a7131f22bf44a074e545480f8176a97 100644
--- a/rtree-c/test/expected/for/reduction/r01010.c
+++ b/rtree-c/test/expected/for/reduction/r010100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r010100.c.hs b/rtree-c/test/expected/for/reduction/r010100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010100.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/r010101.c
similarity index 83%
rename from rtree-c/test/expected/for/reduction/r01011.c
rename to rtree-c/test/expected/for/reduction/r010101.c
index af38507c335d9fd6f57d81acd467af1c85ab8bc4..c2b38ac53a4947904f96c8f80e7afbf6b984ea71 100644
--- a/rtree-c/test/expected/for/reduction/r01011.c
+++ b/rtree-c/test/expected/for/reduction/r010101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r010101.c.hs b/rtree-c/test/expected/for/reduction/r010101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010101.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/r0101100.c b/rtree-c/test/expected/for/reduction/r0101100.c
new file mode 100644
index 0000000000000000000000000000000000000000..d2c4508c623e1756e1e889239bf665cd9afa33a4
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0101100.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0101100.c.hs b/rtree-c/test/expected/for/reduction/r0101100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0101100.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/r01011010.c b/rtree-c/test/expected/for/reduction/r01011010.c
new file mode 100644
index 0000000000000000000000000000000000000000..9484835837448f1299f735a131ea7a3d90b27af6
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01011010.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01011010.c.hs b/rtree-c/test/expected/for/reduction/r01011010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01011010.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/r010110110.c b/rtree-c/test/expected/for/reduction/r010110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..a93abcce913dedc6f875972b1fa1e6257800465b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010110110.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010110110.c.hs b/rtree-c/test/expected/for/reduction/r010110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010110110.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/r010110111.c b/rtree-c/test/expected/for/reduction/r010110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..295d6db53eaec11accd5be1d7474b5dad764b968
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010110111.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010110111.c.hs b/rtree-c/test/expected/for/reduction/r010110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010110111.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/r0101110.c b/rtree-c/test/expected/for/reduction/r0101110.c
new file mode 100644
index 0000000000000000000000000000000000000000..95d45844b0acee1c8836f891787193b7ccd6542e
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0101110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0101110.c.hs b/rtree-c/test/expected/for/reduction/r0101110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0101110.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/r01011110.c b/rtree-c/test/expected/for/reduction/r01011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..55c6663600235be355eebd37e9211a00ca4cd5ae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01011110.c
@@ -0,0 +1,15 @@
+// 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 declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r01011110.c.hs b/rtree-c/test/expected/for/reduction/r01011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01011110.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/r010111110.c b/rtree-c/test/expected/for/reduction/r010111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..009a6a55e1ba7db92e080a3c59b73d3438b3f588
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010111110.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010111110.c.hs b/rtree-c/test/expected/for/reduction/r010111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010111110.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/r010111111.c b/rtree-c/test/expected/for/reduction/r010111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..a54ac8285749db52da7838e0cdeefd4739f30aaa
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010111111.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)
+// 1 reduce to left at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r010111111.c.hs b/rtree-c/test/expected/for/reduction/r010111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r010111111.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/r0110.c b/rtree-c/test/expected/for/reduction/r01100.c
similarity index 81%
rename from rtree-c/test/expected/for/reduction/r0110.c
rename to rtree-c/test/expected/for/reduction/r01100.c
index a89475b65a4fee33bd198b6e75dc83fd91244cf3..43f6e0096b53a6aeae5a2affd67f6c76ebd5367d 100644
--- a/rtree-c/test/expected/for/reduction/r0110.c
+++ b/rtree-c/test/expected/for/reduction/r01100.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 declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r01100.c.hs b/rtree-c/test/expected/for/reduction/r01100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01100.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/r01101.c
similarity index 81%
rename from rtree-c/test/expected/for/reduction/r0111.c
rename to rtree-c/test/expected/for/reduction/r01101.c
index d936ce0895ca1c81f6fb972b9e4df017567401b5..dac4ee8f9a68fe94943c374248fdf8f7d143701c 100644
--- a/rtree-c/test/expected/for/reduction/r0111.c
+++ b/rtree-c/test/expected/for/reduction/r01101.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 declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int a = 0;
diff --git a/rtree-c/test/expected/for/reduction/r01101.c.hs b/rtree-c/test/expected/for/reduction/r01101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01101.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/r011100.c b/rtree-c/test/expected/for/reduction/r011100.c
new file mode 100644
index 0000000000000000000000000000000000000000..c9e31991f3745a2a3538ad6cda62a5c124c46012
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r011100.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r011100.c.hs b/rtree-c/test/expected/for/reduction/r011100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r011100.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/r0111010.c b/rtree-c/test/expected/for/reduction/r0111010.c
new file mode 100644
index 0000000000000000000000000000000000000000..ccf782ecc8cfc38df6cf3de536383f59b434a4ec
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0111010.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0111010.c.hs b/rtree-c/test/expected/for/reduction/r0111010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0111010.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/r01110110.c b/rtree-c/test/expected/for/reduction/r01110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..13d066750a63a232432c0bb97bfc79b5335ad091
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01110110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r01110110.c.hs b/rtree-c/test/expected/for/reduction/r01110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01110110.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/r01110111.c b/rtree-c/test/expected/for/reduction/r01110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..e8d3e2d60e321193be5402fb03f4139899b6a35c
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01110111.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r01110111.c.hs b/rtree-c/test/expected/for/reduction/r01110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01110111.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/r011110.c b/rtree-c/test/expected/for/reduction/r011110.c
new file mode 100644
index 0000000000000000000000000000000000000000..dc0e91ac8f86d34f5c9e9a3c7a6f286474241734
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r011110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r011110.c.hs b/rtree-c/test/expected/for/reduction/r011110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r011110.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/r0111110.c b/rtree-c/test/expected/for/reduction/r0111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..a9f1a5fe5848abcf26fc91dd6a3f8a9e8f95a11b
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0111110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int a = 0;
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r0111110.c.hs b/rtree-c/test/expected/for/reduction/r0111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r0111110.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/r01111110.c b/rtree-c/test/expected/for/reduction/r01111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..363f67021d9dffc7be694fc8bfe33f5fa8d0fc2e
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01111110.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r01111110.c.hs b/rtree-c/test/expected/for/reduction/r01111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01111110.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/r01111111.c b/rtree-c/test/expected/for/reduction/r01111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..181bd26a661aedb96244eb12f357e561a3c78fbb
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01111111.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)
+// 1 remove initializer at ("test/cases/small/for.c": line 4)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int a = 0;
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r01111111.c.hs b/rtree-c/test/expected/for/reduction/r01111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r01111111.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/r10.c b/rtree-c/test/expected/for/reduction/r100.c
similarity index 71%
rename from rtree-c/test/expected/for/reduction/r10.c
rename to rtree-c/test/expected/for/reduction/r100.c
index 8c7a31caf85b194da7847492f57adfc4098afc50..50e1a8b469ab610103e9ee43d48c2859fc89e367 100644
--- a/rtree-c/test/expected/for/reduction/r10.c
+++ b/rtree-c/test/expected/for/reduction/r100.c
@@ -1,4 +1,5 @@
 // 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 0 remove empty declaration at ("test/cases/small/for.c": line 4)
 // 0 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int main()
diff --git a/rtree-c/test/expected/for/reduction/r100.c.hs b/rtree-c/test/expected/for/reduction/r100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r100.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/r101.c
similarity index 71%
rename from rtree-c/test/expected/for/reduction/r11.c
rename to rtree-c/test/expected/for/reduction/r101.c
index c3507ba9463d58e295a3e8d403af2eec7875fdf0..13efffc4f2a734d4d13a1f351802634216909ed2 100644
--- a/rtree-c/test/expected/for/reduction/r11.c
+++ b/rtree-c/test/expected/for/reduction/r101.c
@@ -1,4 +1,5 @@
 // 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 0 remove empty declaration at ("test/cases/small/for.c": line 4)
 // 1 remove empty compound at ("test/cases/small/for.c": line 4)
 
 int main()
diff --git a/rtree-c/test/expected/for/reduction/r101.c.hs b/rtree-c/test/expected/for/reduction/r101.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r101.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/r1100.c b/rtree-c/test/expected/for/reduction/r1100.c
new file mode 100644
index 0000000000000000000000000000000000000000..a28e65fe77cb4bfae5b2fa913e9d6fbd797f2fc0
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r1100.c
@@ -0,0 +1,11 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r1100.c.hs b/rtree-c/test/expected/for/reduction/r1100.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r1100.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/r11010.c b/rtree-c/test/expected/for/reduction/r11010.c
new file mode 100644
index 0000000000000000000000000000000000000000..8f376c8e374f0f57cddf61f0762dcde90fa08561
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r11010.c
@@ -0,0 +1,11 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r11010.c.hs b/rtree-c/test/expected/for/reduction/r11010.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r11010.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/r110110.c b/rtree-c/test/expected/for/reduction/r110110.c
new file mode 100644
index 0000000000000000000000000000000000000000..532cc58917a45d7ccb6a78cdaf72154280ee6f64
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r110110.c
@@ -0,0 +1,10 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r110110.c.hs b/rtree-c/test/expected/for/reduction/r110110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r110110.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/r110111.c b/rtree-c/test/expected/for/reduction/r110111.c
new file mode 100644
index 0000000000000000000000000000000000000000..9398be6240d17488925a16fea61732c9c8a7d79d
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r110111.c
@@ -0,0 +1,10 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r110111.c.hs b/rtree-c/test/expected/for/reduction/r110111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r110111.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/r1110.c b/rtree-c/test/expected/for/reduction/r1110.c
new file mode 100644
index 0000000000000000000000000000000000000000..0178bd1a355bcab50d2776b153ed0ec78906d2f2
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r1110.c
@@ -0,0 +1,11 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 0 remove the for loop at ("test/cases/small/for.c": line 4)
+
+int main()
+{
+    for (;;)
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r1110.c.hs b/rtree-c/test/expected/for/reduction/r1110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r1110.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/r11110.c b/rtree-c/test/expected/for/reduction/r11110.c
new file mode 100644
index 0000000000000000000000000000000000000000..58075d08c83b501c69b40e87bd2932cedf18b831
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r11110.c
@@ -0,0 +1,11 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 0 expand compound statment at ("test/cases/small/for.c": line 4)
+
+int main()
+{
+    {
+    }
+}
diff --git a/rtree-c/test/expected/for/reduction/r11110.c.hs b/rtree-c/test/expected/for/reduction/r11110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r11110.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/r111110.c b/rtree-c/test/expected/for/reduction/r111110.c
new file mode 100644
index 0000000000000000000000000000000000000000..6cb7defb9e0b723f5f8b7e49f7362f181368ddaf
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r111110.c
@@ -0,0 +1,10 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 0 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r111110.c.hs b/rtree-c/test/expected/for/reduction/r111110.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r111110.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/r111111.c b/rtree-c/test/expected/for/reduction/r111111.c
new file mode 100644
index 0000000000000000000000000000000000000000..e01c6ccc7dbb63967e3b732ddba00ec625f74cb6
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r111111.c
@@ -0,0 +1,10 @@
+// 1 inline variable a at ("test/cases/small/for.c": line 1)
+// 1 remove empty declaration at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 4)
+// 1 remove the for loop at ("test/cases/small/for.c": line 4)
+// 1 expand compound statment at ("test/cases/small/for.c": line 4)
+// 1 remove empty compound at ("test/cases/small/for.c": line 3)
+
+int main()
+{
+}
diff --git a/rtree-c/test/expected/for/reduction/r111111.c.hs b/rtree-c/test/expected/for/reduction/r111111.c.hs
new file mode 100644
index 0000000000000000000000000000000000000000..844af64c03a13962bd019fffbee88229c2fa5fae
--- /dev/null
+++ b/rtree-c/test/expected/for/reduction/r111111.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 [] [] () ) ()
+                    )
+                ] ()
+            ) ()
+        )
+    ] ()