diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc
index 064ef8f272b2ccd88804d7f560410f38d291a5fd..3f5eb94b619ea8ba4abb29e2202e090067f24d59 100644
--- a/gcc/cobol/genapi.cc
+++ b/gcc/cobol/genapi.cc
@@ -47,15 +47,6 @@
 #include "valconv.h"
 #include "show_parse.h"
 
-// This structure is returned by the parser_performxxx() routines, and gets
-// handed to the parser_perform_modify routines
-struct cbl_parser_mod
-  {
-  tree_stmt_iterator tsi_goto;
-  tree_stmt_iterator tsi_retadd;
-  tree_stmt_iterator tsi_label;
-  } ;
-
 #define TSI_BACK (tsi_last(current_function->statement_list_stack.back()))
 
 //#define XXX do{gg_printf("LINE %d\n", build_int_cst_type(INT, __LINE__), NULL_TREE);}while(0);
@@ -2993,11 +2984,10 @@ parser_perform(cbl_label_t *label, bool suppress_nexting)
                                   return_address_decl);
   tree return_addr = gg_get_address_of(return_address_decl);
 
-  cbl_parser_mod *parser_mod = new cbl_parser_mod;
+//  cbl_parser_mod *parser_mod = new cbl_parser_mod;
 
   // Put the return address onto the pseudo-return stack
   pseudo_return_push(procedure, return_addr);
-  parser_mod->tsi_retadd = TSI_BACK;
 
   // Create the code that will launch the paragraph
   // The following comment is, believe it or not, necessary.  The insertion
@@ -3052,11 +3042,8 @@ parser_perform(cbl_label_t *label, bool suppress_nexting)
   // local symbol, and crashes.
   gg_goto(procedure->top.addr);
 
-  parser_mod->tsi_goto = TSI_BACK;
-
   // And create the return address label:
   gg_append_statement(return_label_expr);
-  parser_mod->tsi_goto = TSI_BACK;
   TRACE1
     {
     TRACE1_HEADER
diff --git a/gcc/cobol/gengen.cc b/gcc/cobol/gengen.cc
index d90e3199cf4fd5eef99870de8e89b7c27e33021c..83af93c1422b6278449a43257bda2cb22e897393 100644
--- a/gcc/cobol/gengen.cc
+++ b/gcc/cobol/gengen.cc
@@ -296,17 +296,6 @@ gg_append_statement(tree stmt)
   append_to_statement_list( stmt, &(current_function->statement_list_stack.back()) );
   }
 
-void
-gg_insert_statement(struct tree_stmt_iterator *tsi, tree stmt)
-  {
-  // Instead of appending to the end, we insert after tsi.  This function was
-  // created to implement parser_perform_modify()
-
-  TREE_SIDE_EFFECTS(stmt) = 1;    // If an expression has no side effects,
-  //                              // it won't generate code.
-  tsi_link_after (tsi, stmt, TSI_CONTINUE_LINKING);
-  }
-
 tree
 gg_float(tree floating_type, tree integer_var)
   {
@@ -476,68 +465,6 @@ gg_assign(tree dest, const tree source)
     }
   }
 
-void
-gg_assign_insert(struct tree_stmt_iterator *tsi, tree dest, const tree source)
-  {
-  saw_pointer = false;
-  tree dest_type = adjust_for_type(TREE_TYPE(dest));
-  bool p1 = saw_pointer;
-  saw_pointer = false;
-  tree source_type = adjust_for_type(TREE_TYPE(source));
-  bool p2 = saw_pointer;
-
-  if( getenv("X2") )
-    {
-    fprintf(stderr,"dest is %s%s;", show_type(dest_type), p1 ? "_P" : "");
-    fprintf(stderr," source is %s%s\n", show_type(source_type), p2 ? "_P" : "");
-    }
-
-  bool okay = dest_type == source_type;
-
-  if( !okay )
-    {
-    if(    TREE_CODE(dest_type)   == INTEGER_TYPE
-           && TREE_CODE(source_type) == INTEGER_TYPE
-           && TREE_INT_CST_LOW(TYPE_SIZE(dest_type)) == TREE_INT_CST_LOW(TYPE_SIZE(source_type))
-           && TYPE_UNSIGNED(dest_type) == TYPE_UNSIGNED(source_type) )
-      {
-      okay = true;
-      }
-    }
-
-  if( okay )
-    {
-    tree stmt = build2_loc( location_from_lineno(),
-                            MODIFY_EXPR,
-                            TREE_TYPE(dest),
-                            dest,
-                            source);
-    gg_insert_statement(tsi, stmt);
-    }
-  else
-    {
-    if( getenv("X1") )
-      {
-      warnx("Inefficient assignment");
-      if(DECL_P(dest) && DECL_NAME(dest))
-        {
-        warnx("Destination is %s", IDENTIFIER_POINTER(DECL_NAME(dest)));
-        }
-      gcc_assert(false);
-      }
-
-    // The C equivalent would be "dest = source"
-    // Note that we cast the source to the type of the dest
-    tree stmt = build2_loc( location_from_lineno(),
-                            MODIFY_EXPR,
-                            TREE_TYPE(dest),
-                            dest,
-                            gg_cast(TREE_TYPE(dest), source)
-                          );
-    gg_insert_statement(tsi, stmt);
-    }
-  }
-
 tree
 gg_find_field_in_struct(const tree base, const char *field_name)
   {
diff --git a/gcc/cobol/gengen.h b/gcc/cobol/gengen.h
index 2ac57e741d3a54236aa281228a733a719a7ea168..a03f46576852b2fb4bb862d7185271bf2ebd1bc5 100644
--- a/gcc/cobol/gengen.h
+++ b/gcc/cobol/gengen.h
@@ -294,7 +294,7 @@ extern void gg_build_translation_unit(const char *filename);
 // runtime binary, it has to find its way onto a statement list.  (Or be used
 // as the second operand of a modify_expr, and so on.)
 extern void gg_append_statement(tree stmt);
-extern void gg_insert_statement(struct tree_stmt_iterator *tsi, tree stmt);
+//// extern void gg_insert_statement(struct tree_stmt_iterator *tsi, tree stmt);
 
 // For variables:
 extern void gg_append_var_decl(tree var);
@@ -306,9 +306,6 @@ extern tree gg_cast(tree type, tree var);
 
 // Assignment, that is to say, A = B
 extern void gg_assign(tree dest, const tree source);
-extern void gg_assign_insert( struct tree_stmt_iterator *tsi,
-                              tree dest,
-                              const tree source);
 
 // struct creation and field access
 // Create struct, and access a field in a struct
diff --git a/libgcobol/libgcobol.h b/libgcobol/libgcobol.h
index dbe7e53565ef81eb7037097bb687691397ad3ab9..c44fc2656c7d338d3190e690bd70839a90b7f738 100644
--- a/libgcobol/libgcobol.h
+++ b/libgcobol/libgcobol.h
@@ -54,13 +54,6 @@
 
 #define A_ZILLION (1000000) // Absurdly large number for __gg__call_parameter_count
 
-//// // These are used by parser_call() and parser_division(procedure_div_e) to
-//// // understand what arguments are being passed as formal parameters to
-//// // function-id's and program-id's
-//// #define ARGUMENT_POINTER      (1ULL<<63)
-//// #define ARGUMENT_FLOAT        (1ULL<<62)
-//// #define ARGUMENT_LENGTH_MASK ((1ULL<<62)-1ULL)
-
 // These bits are used for the "call flags" of arithmetic operations
 #define ON_SIZE_ERROR 0x01
 #define REMAINDER_PRESENT 0x02