From 389e41f3ee011b3092a4841b0711dc8b68eccbca Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Fri, 24 Jan 2025 15:24:23 -0500
Subject: [PATCH] Improved Make-lang.in for charmaps- and valconv-dup. New
 errmsg for missing main()

---
 gcc/cobol/.gitignore                    |   4 +-
 gcc/cobol/Make-lang.in                  |  23 +-
 gcc/cobol/UAT/testsuite.src/syn_misc.at |  10 +-
 gcc/cobol/charmaps-copy.cc              | 929 ------------------------
 gcc/cobol/genapi.cc                     |   7 -
 5 files changed, 16 insertions(+), 957 deletions(-)
 delete mode 100644 gcc/cobol/charmaps-copy.cc

diff --git a/gcc/cobol/.gitignore b/gcc/cobol/.gitignore
index 514f368b30a9..b9dc95a2c638 100644
--- a/gcc/cobol/.gitignore
+++ b/gcc/cobol/.gitignore
@@ -10,5 +10,5 @@ nist/obj
 dump.txt
 .gawk_history
 .gawkrc
-charmaps-copy.cc
-valconv-copy.cc
+charmaps-dupe.cc
+valconv-dupe.cc
diff --git a/gcc/cobol/Make-lang.in b/gcc/cobol/Make-lang.in
index 95e2dec3be5e..3c5e66f0e5b2 100644
--- a/gcc/cobol/Make-lang.in
+++ b/gcc/cobol/Make-lang.in
@@ -47,6 +47,7 @@ cobol: cobol1$(exeext)
 
 BINCLUDE ?= ./gcc
 LIB_INCLUDE ?= $(srcdir)/../libgcobol
+LIB_SOURCE ?= $(srcdir)/../libgcobol
 
 #
 # At this point, as of 2022-10-21, CPPFLAGS is an empty string and can be
@@ -93,13 +94,8 @@ cobol_one_OBJS =    \
  cobol/symbols.o    \
  cobol/symfind.o    \
  cobol/util.o       \
- cobol/charmaps-copy.o   \
- cobol/valconv-copy.o    \
- $(END)
-
-cobol_OBJS_FROM_LIBGCOBOL = \
- cobol/charmaps-copy.o           \
- cobol/valconv-copy.o            \
+ cobol/charmaps-dupe.o   \
+ cobol/valconv-dupe.o    \
  $(END)
 
 #
@@ -109,11 +105,11 @@ cobol_OBJS_FROM_LIBGCOBOL = \
 # the gcc/cobol build tree.  This avoids the nightmare of one file appearing in
 # more than one place.
 #
-../../gcc/cobol/charmaps-copy.cc: ../libgcobol/charmaps.cc
+$(srcdir)/cobol/charmaps-dupe.cc: $(LIB_SOURCE)/charmaps.cc
 	echo "// DO NOT EDIT THIS FILE.  It was copied from the libgcobol directory." > $@
 	tail -n +2 $< >> $@
 
-../../gcc/cobol/valconv-copy.cc: ../libgcobol/valconv.cc
+$(srcdir)/cobol/valconv-dupe.cc: $(LIB_SOURCE)/valconv.cc
 	echo "// DO NOT EDIT THIS FILE.  It was copied from the libgcobol directory." > $@
 	tail -n +2 $< >> $@
 
@@ -130,7 +126,6 @@ GCOBOL_D_OBJS = $(GCC_OBJS) cobol/gcobolspec.o
 #
 
 cobol_OBJS = \
-   $(cobol_OBJS_FROM_LIBGCOBOL) \
    $(cobol_one_OBJS) \
    cobol/gcobolspec.o \
    $(END)
@@ -148,7 +143,6 @@ CFLAGS-cobol/gcobolspec.o += $(DRIVER_DEFINES)
 gcobol$(exeext): \
 	 $(GCOBOL_D_OBJS) \
 	 $(EXTRA_GCC_OBJS) \
-     $(cobol_OBJS_FROM_LIBGCOBOL) \
      libcommon-target.a \
      $(LIBDEPS)
 	+$(LINKER) $(ALL_LINKERFLAGS) $(LDFLAGS) -o $@		\
@@ -258,8 +252,7 @@ cobol/scan.o: cobol/scan.c			\
 
 # And the cobol1.exe front end
 
-cobol1$(exeext): $(cobol_one_OBJS) $(cobol_OBJS_FROM_LIBGCOBOL) \
-	$(BACKEND) $(LIBDEPS) attribs.o
+cobol1$(exeext): $(cobol_one_OBJS) 	$(BACKEND) $(LIBDEPS) attribs.o
 	+$(LLINKER) $(ALL_LINKERFLAGS) $(LDFLAGS) attribs.o -o $@	\
 	      $(cobol_one_OBJS) $(BACKEND) $(LIBS) $(BACKENDLIBS)
 
@@ -307,8 +300,8 @@ cobol.mostlyclean:
 cobol.clean:
 	rm -fr cobol1 cobol/*              \
 	../*/libgcobol/*                   \
-	../../gcc/cobol/charmaps-copy.cc   \
-	../../gcc/cobol/valconv-copy.cc    \
+	$(srcdir)/cobol/charmaps-dupe.cc   \
+	$(srcdir)/cobol/valconv-dupe.cc    \
 
 cobol.distclean:
 
diff --git a/gcc/cobol/UAT/testsuite.src/syn_misc.at b/gcc/cobol/UAT/testsuite.src/syn_misc.at
index 33c12c93e4ac..4bdea7083fa0 100644
--- a/gcc/cobol/UAT/testsuite.src/syn_misc.at
+++ b/gcc/cobol/UAT/testsuite.src/syn_misc.at
@@ -1092,10 +1092,12 @@ AT_DATA([prog.cob], [        identification division.
         end program prog.
         end function func.
 ])
-AT_CHECK([$COMPILE prog.cob], [1], [], [prog.cob:14:1: error: -main switch says "prog.cob" should contain the starting program, but none was found
-   14 |         end function func.
-      | ^
-])
+AT_CHECK([$COMPILE prog.cob], [1], [], stderr)
+AT_CHECK([sed -e "s/^.*\(in function \`_start'\).*$/\1/g" -e "s/^.*\(undefined reference to \`main'\).*$/\1/g" stderr], [0], 
+[in function `_start'
+undefined reference to `main'
+collect2: error: ld returned 1 exit status
+], [])
 AT_CLEANUP
 
 AT_SETUP([DECLARATIVES with following SECTION])
diff --git a/gcc/cobol/charmaps-copy.cc b/gcc/cobol/charmaps-copy.cc
deleted file mode 100644
index b05791bcd245..000000000000
--- a/gcc/cobol/charmaps-copy.cc
+++ /dev/null
@@ -1,929 +0,0 @@
-// DO NOT EDIT THIS FILE.  It was copied from the libgcobol directory.
-/*
- * Copyright (c) 2021-2024 Symas Corporation
- *
- * Redistribution and use in source and binary forms, with or without
- * modification, are permitted provided that the following conditions are
- * met:
- *
- * * Redistributions of source code must retain the above copyright
- *   notice, this list of conditions and the following disclaimer.
- * * Redistributions in binary form must reproduce the above
- *   copyright notice, this list of conditions and the following disclaimer
- *   in the documentation and/or other materials provided with the
- *   distribution.
- * * Neither the name of the Symas Corporation nor the names of its
- *   contributors may be used to endorse or promote products derived from
- *   this software without specific prior written permission.
- *
- * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
- * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
- * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
- * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
- * OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
- * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
- * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
- * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
- * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
- * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
- * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
- */
-
-#include <ctype.h>
-#include <errno.h>
-#include <fcntl.h>
-#include <math.h>
-#include <stdio.h>
-#include <stdlib.h>
-#include <string.h>
-#include <time.h>
-#include <unistd.h>
-#include <algorithm>
-#include <langinfo.h>
-#include <unordered_map>
-#include <locale.h>
-#include <iconv.h>
-
-#include "ec.h"
-#include "common-defs.h"
-#include "io.h"
-#include "gcobolio.h"
-#include "libgcobol.h"
-#include "charmaps.h"
-#include "valconv.h"
-
-// First: single-byte-coded (SBC) character sets:
-
-// 7-bit ASCII is a subset of the various ISO/IEC 8859 code pages.
-// 8859 is a subset of code page 1252.
-// CP1252 is informally, and improperly, known as the "ANSI" code set.  In
-// modern usage, when somebody says "8859-1", they almost invariably are
-// referring to a CP1252 code set.
-
-// EBCDIC is also an SBC character set.  IBM's original "international EBCDIC"
-// code set was Code Page 37, which did not have a Euro sign.  Code Page 1140
-// is the same as CP37, but with the Euro sign replacing the "universal
-// currency symbol" at position 0x9F.  The table below maps the 256 values of
-// CodePage 1140 to the 256 values of CodePage 1252 in a way that allows for
-// "round trip" conversion without any loss.
-
-// See https://en.wikipedia.org/w/index.php?title=Code_page_37&oldid=1082467670,
-
-// The modern world increasingly uses UTF-8, which is in conflict with ordinary
-// COBOL's inherently single-byte nature.  In UTF-8, the encoding for a Euro
-// sign is three bytes (U+20AC encodes to E2 A2 AC).  In single-byte CP1252, the
-// Euro is encoded as 0x80.
-
-// So, we are going to assume that internally, the generated COBOL executable
-// operates in code page 1252 or [hopefully some day] code page 1140.
-
-// We will convert output, as in DISPLAY <something> from the internal character
-// set to the running machine's locale (for now, that locale will be assumed to
-// be 1252/8859 if it isn't UTF-8).
-
-// And we will take some pains to figure out if the source code file was done
-// as UTF-8; if not, we will assume 1252/8859-1
-
-// __gg__ebcdic_codeset_in_use is the ultimate determinator of whether the
-// internal codeset is ASCII/CP1252 or EBCDIC/CP1140.
-bool __gg__ebcdic_codeset_in_use = false ;
-
-static text_codeset_t source_codeset  = cs_cp1252_e;
-static text_codeset_t console_codeset = cs_default_e;
-
-#define UNICODE_REPLACEMENT 0xFFFD  // This a white question mark in a black diamond
-#define ASCII_REPLACEMENT 0x87     // In CP1252, 0x87 is a double-dagger
-
-// This table is the default one-to-one mapping that's used, for example, when
-// starting with ASCII and doing ASCII comparisons:
-
-const unsigned short
-__gg__one_to_one_values[256] =
-    {
-    0x00,0x01,0x02,0x03,0x04,0x05,0x06,0x07,0x08,0x09,0x0A,0x0B,0x0C,0x0D,0x0E,0x0F,
-    0x10,0x11,0x12,0x13,0x14,0x15,0x16,0x17,0x18,0x19,0x1A,0x1B,0x1C,0x1D,0x1E,0x1F,
-    0x20,0x21,0x22,0x23,0x24,0x25,0x26,0x27,0x28,0x29,0x2A,0x2B,0x2C,0x2D,0x2E,0x2F,
-    0x30,0x31,0x32,0x33,0x34,0x35,0x36,0x37,0x38,0x39,0x3A,0x3B,0x3C,0x3D,0x3E,0x3F,
-    0x40,0x41,0x42,0x43,0x44,0x45,0x46,0x47,0x48,0x49,0x4A,0x4B,0x4C,0x4D,0x4E,0x4F,
-    0x50,0x51,0x52,0x53,0x54,0x55,0x56,0x57,0x58,0x59,0x5A,0x5B,0x5C,0x5D,0x5E,0x5F,
-    0x60,0x61,0x62,0x63,0x64,0x65,0x66,0x67,0x68,0x69,0x6A,0x6B,0x6C,0x6D,0x6E,0x6F,
-    0x70,0x71,0x72,0x73,0x74,0x75,0x76,0x77,0x78,0x79,0x7A,0x7B,0x7C,0x7D,0x7E,0x7F,
-    0x80,0x81,0x82,0x83,0x84,0x85,0x86,0x87,0x88,0x89,0x8A,0x8B,0x8C,0x8D,0x8E,0x8F,
-    0x90,0x91,0x92,0x93,0x94,0x95,0x96,0x97,0x98,0x99,0x9A,0x9B,0x9C,0x9D,0x9E,0x9F,
-    0xA0,0xA1,0xA2,0xA3,0xA4,0xA5,0xA6,0xA7,0xA8,0xA9,0xAA,0xAB,0xAC,0xAD,0xAE,0xAF,
-    0xB0,0xB1,0xB2,0xB3,0xB4,0xB5,0xB6,0xB7,0xB8,0xB9,0xBA,0xBB,0xBC,0xBD,0xBE,0xBF,
-    0xC0,0xC1,0xC2,0xC3,0xC4,0xC5,0xC6,0xC7,0xC8,0xC9,0xCA,0xCB,0xCC,0xCD,0xCE,0xCF,
-    0xD0,0xD1,0xD2,0xD3,0xD4,0xD5,0xD6,0xD7,0xD8,0xD9,0xDA,0xDB,0xDC,0xDD,0xDE,0xDF,
-    0xE0,0xE1,0xE2,0xE3,0xE4,0xE5,0xE6,0xE7,0xE8,0xE9,0xEA,0xEB,0xEC,0xED,0xEE,0xEF,
-    0xF0,0xF1,0xF2,0xF3,0xF4,0xF5,0xF6,0xF7,0xF8,0xF9,0xFA,0xFB,0xFC,0xFD,0xFE,0xFF
-    };
-
-// This table can be used for converting EBCDIC values to CP1252.
-
-// There is an unfortunate caveat, one that undoubtedly will have unintended
-// consequences.  But COBOL has has the concept of a HIGH-VALUE, a character
-// that theoretically tests alphanumercially greater than all other characters.
-// In the CP1252 code page, the default HIGH-VALUE (it can be changed by the
-// ALPHABET clause is 0xFF, which is displayed as the character 'ÿ').  In the
-// EBCDIC code page 1140, that character is an EO control code.
-
-// So. In order that the default HIGH-VALUE once and always is 0xFF, these
-// two tables have been modified slightly so that 0xFF always maps to 0xFF
-
-// Programmers who use the ALPHABET clause to change the HIGH-VALUE are on their
-// own.
-
-
-const unsigned short
-__gg__cp1140_to_cp1252_values[256] =
-    {
-    0x00, 0x01, 0x02, 0x03, 0x9C, 0x09, 0x86, 0x7F, 0x97, 0x8D, 0x8E, 0x0B, 0x0C, 0x0D, 0x0E, 0x0F,
-    0x10, 0x11, 0x12, 0x13, 0x9D, 0x85, 0x08, 0x87, 0x18, 0x19, 0x92, 0x8F, 0x1C, 0x1D, 0x1E, 0x1F,
-    0xA4, 0x81, 0x82, 0x83, 0x84, 0x0A, 0x17, 0x1B, 0x88, 0x89, 0x8A, 0x8B, 0x8C, 0x05, 0x06, 0x07,
-    0x90, 0x91, 0x16, 0x93, 0x94, 0x95, 0x96, 0x04, 0x98, 0x99, 0x9A, 0x9B, 0x14, 0x15, 0x9E, 0x1A,
-    0x20, 0xA0, 0xE2, 0xE4, 0xE0, 0xE1, 0xE3, 0xE5, 0xE7, 0xF1, 0xA2, 0x2E, 0x3C, 0x28, 0x2B, 0x7C,
-    0x26, 0xE9, 0xEA, 0xEB, 0xE8, 0xED, 0xEE, 0xEF, 0xEC, 0xDF, 0x21, 0x24, 0x2A, 0x29, 0x3B, 0xAC,
-    0x2D, 0x2F, 0xC2, 0xC4, 0xC0, 0xC1, 0xC3, 0xC5, 0xC7, 0xD1, 0xA6, 0x2C, 0x25, 0x5F, 0x3E, 0x3F,
-    0xF8, 0xC9, 0xCA, 0xCB, 0xC8, 0xCD, 0xCE, 0xCF, 0xCC, 0x60, 0x3A, 0x23, 0x40, 0x27, 0x3D, 0x22,
-    0xD8, 0x61, 0x62, 0x63, 0x64, 0x65, 0x66, 0x67, 0x68, 0x69, 0xAB, 0xBB, 0xF0, 0xFD, 0xFE, 0xB1,
-    0xB0, 0x6A, 0x6B, 0x6C, 0x6D, 0x6E, 0x6F, 0x70, 0x71, 0x72, 0xAA, 0xBA, 0xE6, 0xB8, 0xC6, 0x80,
-    0xB5, 0x7E, 0x73, 0x74, 0x75, 0x76, 0x77, 0x78, 0x79, 0x7A, 0xA1, 0xBF, 0xD0, 0xDD, 0xDE, 0xAE,
-    0x5E, 0xA3, 0xA5, 0xB7, 0xA9, 0xA7, 0xB6, 0xBC, 0xBD, 0xBE, 0x5B, 0x5D, 0xAF, 0xA8, 0xB4, 0xD7,
-    0x7B, 0x41, 0x42, 0x43, 0x44, 0x45, 0x46, 0x47, 0x48, 0x49, 0xAD, 0xF4, 0xF6, 0xF2, 0xF3, 0xF5,
-    0x7D, 0x4A, 0x4B, 0x4C, 0x4D, 0x4E, 0x4F, 0x50, 0x51, 0x52, 0xB9, 0xFB, 0xFC, 0xF9, 0xFA, 0xFF,
-    0x5C, 0xF7, 0x53, 0x54, 0x55, 0x56, 0x57, 0x58, 0x59, 0x5A, 0xB2, 0xD4, 0xD6, 0xD2, 0xD3, 0xD5,
-    0x30, 0x31, 0x32, 0x33, 0x34, 0x35, 0x36, 0x37, 0x38, 0x39, 0xB3, 0xDB, 0xDC, 0xD9, 0xDA, /*0x9F*/ 0xFF,
-    };
-
-// This table is the mirror image of cp1140_to_cp1252_values, except for the
-// above-mentioned 0xFF
-const unsigned short
-__gg__cp1252_to_cp1140_values[256] =
-    {
-    0x00, 0x01, 0x02, 0x03, 0x37, 0x2D, 0x2E, 0x2F, 0x16, 0x05, 0x25, 0x0B, 0x0C, 0x0D, 0x0E, 0x0F,
-    0x10, 0x11, 0x12, 0x13, 0x3C, 0x3D, 0x32, 0x26, 0x18, 0x19, 0x3F, 0x27, 0x1C, 0x1D, 0x1E, 0x1F,
-    0x40, 0x5A, 0x7F, 0x7B, 0x5B, 0x6C, 0x50, 0x7D, 0x4D, 0x5D, 0x5C, 0x4E, 0x6B, 0x60, 0x4B, 0x61,
-    0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5, 0xF6, 0xF7, 0xF8, 0xF9, 0x7A, 0x5E, 0x4C, 0x7E, 0x6E, 0x6F,
-    0x7C, 0xC1, 0xC2, 0xC3, 0xC4, 0xC5, 0xC6, 0xC7, 0xC8, 0xC9, 0xD1, 0xD2, 0xD3, 0xD4, 0xD5, 0xD6,
-    0xD7, 0xD8, 0xD9, 0xE2, 0xE3, 0xE4, 0xE5, 0xE6, 0xE7, 0xE8, 0xE9, 0xBA, 0xE0, 0xBB, 0xB0, 0x6D,
-    0x79, 0x81, 0x82, 0x83, 0x84, 0x85, 0x86, 0x87, 0x88, 0x89, 0x91, 0x92, 0x93, 0x94, 0x95, 0x96,
-    0x97, 0x98, 0x99, 0xA2, 0xA3, 0xA4, 0xA5, 0xA6, 0xA7, 0xA8, 0xA9, 0xC0, 0x4F, 0xD0, 0xA1, 0x07,
-    0x9F, 0x21, 0x22, 0x23, 0x24, 0x15, 0x06, 0x17, 0x28, 0x29, 0x2A, 0x2B, 0x2C, 0x09, 0x0A, 0x1B,
-    0x30, 0x31, 0x1A, 0x33, 0x34, 0x35, 0x36, 0x08, 0x38, 0x39, 0x3A, 0x3B, 0x04, 0x14, 0x3E, 0xFF,
-    0x41, 0xAA, 0x4A, 0xB1, 0x20, 0xB2, 0x6A, 0xB5, 0xBD, 0xB4, 0x9A, 0x8A, 0x5F, 0xCA, 0xAF, 0xBC,
-    0x90, 0x8F, 0xEA, 0xFA, 0xBE, 0xA0, 0xB6, 0xB3, 0x9D, 0xDA, 0x9B, 0x8B, 0xB7, 0xB8, 0xB9, 0xAB,
-    0x64, 0x65, 0x62, 0x66, 0x63, 0x67, 0x9E, 0x68, 0x74, 0x71, 0x72, 0x73, 0x78, 0x75, 0x76, 0x77,
-    0xAC, 0x69, 0xED, 0xEE, 0xEB, 0xEF, 0xEC, 0xBF, 0x80, 0xFD, 0xFE, 0xFB, 0xFC, 0xAD, 0xAE, 0x59,
-    0x44, 0x45, 0x42, 0x46, 0x43, 0x47, 0x9C, 0x48, 0x54, 0x51, 0x52, 0x53, 0x58, 0x55, 0x56, 0x57,
-    0x8C, 0x49, 0xCD, 0xCE, 0xCB, 0xCF, 0xCC, 0xE1, 0x70, 0xDD, 0xDE, 0xDB, 0xDC, 0x8D, 0x8E, /*0xDF*/ 0xFF,
-    };
-
-// This is the EBCDIC collating sequence when the internal character set is CP1252.  It's actually
-// a copy of __gg__cp1252_to_cp1140_values, but modified so that 0xFF maps to 0xFF.
-// Doing this meant swapping the CP1252 upper-Y-umlaut with lower-Y-umlaut.
-const unsigned short
-__gg__cp1252_to_ebcdic_collation[256] =
-    {
-    0x00, 0x01, 0x02, 0x03, 0x37, 0x2d, 0x2e, 0x2f, 0x16, 0x05, 0x25, 0x0b, 0x0c, 0x0d, 0x0e, 0x0f,
-    0x10, 0x11, 0x12, 0x13, 0x3c, 0x3d, 0x32, 0x26, 0x18, 0x19, 0x3f, 0x27, 0x1c, 0x1d, 0x1e, 0x1f,
-    0x40, 0x5a, 0x7f, 0x7b, 0x5b, 0x6c, 0x50, 0x7d, 0x4d, 0x5d, 0x5c, 0x4e, 0x6b, 0x60, 0x4b, 0x61,
-    0xf0, 0xf1, 0xf2, 0xf3, 0xf4, 0xf5, 0xf6, 0xf7, 0xf8, 0xf9, 0x7a, 0x5e, 0x4c, 0x7e, 0x6e, 0x6f,
-    0x7c, 0xc1, 0xc2, 0xc3, 0xc4, 0xc5, 0xc6, 0xc7, 0xc8, 0xc9, 0xd1, 0xd2, 0xd3, 0xd4, 0xd5, 0xd6,
-    0xd7, 0xd8, 0xd9, 0xe2, 0xe3, 0xe4, 0xe5, 0xe6, 0xe7, 0xe8, 0xe9, 0xba, 0xe0, 0xbb, 0xb0, 0x6d,
-    0x79, 0x81, 0x82, 0x83, 0x84, 0x85, 0x86, 0x87, 0x88, 0x89, 0x91, 0x92, 0x93, 0x94, 0x95, 0x96,
-    0x97, 0x98, 0x99, 0xa2, 0xa3, 0xa4, 0xa5, 0xa6, 0xa7, 0xa8, 0xa9, 0xc0, 0x4f, 0xd0, 0xa1, 0x07,
-    0x9f, 0x21, 0x22, 0x23, 0x24, 0x15, 0x06, 0x17, 0x28, 0x29, 0x2a, 0x2b, 0x2c, 0x09, 0x0a, 0x1b,
-    0x30, 0x31, 0x1a, 0x33, 0x34, 0x35, 0x36, 0x08, 0x38, 0x39, 0x3a, 0x3b, 0x04, 0x14, 0x3e, 0xdf,
-    0x41, 0xaa, 0x4a, 0xb1, 0x20, 0xb2, 0x6a, 0xb5, 0xbd, 0xb4, 0x9a, 0x8a, 0x5f, 0xca, 0xaf, 0xbc,
-    0x90, 0x8f, 0xea, 0xfa, 0xbe, 0xa0, 0xb6, 0xb3, 0x9d, 0xda, 0x9b, 0x8b, 0xb7, 0xb8, 0xb9, 0xab,
-    0x64, 0x65, 0x62, 0x66, 0x63, 0x67, 0x9e, 0x68, 0x74, 0x71, 0x72, 0x73, 0x78, 0x75, 0x76, 0x77,
-    0xac, 0x69, 0xed, 0xee, 0xeb, 0xef, 0xec, 0xbf, 0x80, 0xfd, 0xfe, 0xfb, 0xfc, 0xad, 0xae, 0x59,
-    0x44, 0x45, 0x42, 0x46, 0x43, 0x47, 0x9c, 0x48, 0x54, 0x51, 0x52, 0x53, 0x58, 0x55, 0x56, 0x57,
-    0x8c, 0x49, 0xcd, 0xce, 0xcb, 0xcf, 0xcc, 0xe1, 0x70, 0xdd, 0xde, 0xdb, 0xdc, 0x8d, 0x8e, 0xff,
-    };
-
-// When using the EBCDIC internal character set, but if told to use the ASCII collating sequence,
-// this table can be used.  It's based on the __gg__cp1140_to_cp1252_values, but with the two
-// characters at locations DF and FF swapped so that the HIGH-VALUE 0xFF maps to 0xFF.
-const unsigned short
-__gg__ebcdic_to_cp1252_collation[256] =
-    {
-    0x00, 0x01, 0x02, 0x03, 0x9C, 0x09, 0x86, 0x7F, 0x97, 0x8D, 0x8E, 0x0B, 0x0C, 0x0D, 0x0E, 0x0F,
-    0x10, 0x11, 0x12, 0x13, 0x9D, 0x85, 0x08, 0x87, 0x18, 0x19, 0x92, 0x8F, 0x1C, 0x1D, 0x1E, 0x1F,
-    0xA4, 0x81, 0x82, 0x83, 0x84, 0x0A, 0x17, 0x1B, 0x88, 0x89, 0x8A, 0x8B, 0x8C, 0x05, 0x06, 0x07,
-    0x90, 0x91, 0x16, 0x93, 0x94, 0x95, 0x96, 0x04, 0x98, 0x99, 0x9A, 0x9B, 0x14, 0x15, 0x9E, 0x1A,
-    0x20, 0xA0, 0xE2, 0xE4, 0xE0, 0xE1, 0xE3, 0xE5, 0xE7, 0xF1, 0xA2, 0x2E, 0x3C, 0x28, 0x2B, 0x7C,
-    0x26, 0xE9, 0xEA, 0xEB, 0xE8, 0xED, 0xEE, 0xEF, 0xEC, 0xDF, 0x21, 0x24, 0x2A, 0x29, 0x3B, 0xAC,
-    0x2D, 0x2F, 0xC2, 0xC4, 0xC0, 0xC1, 0xC3, 0xC5, 0xC7, 0xD1, 0xA6, 0x2C, 0x25, 0x5F, 0x3E, 0x3F,
-    0xF8, 0xC9, 0xCA, 0xCB, 0xC8, 0xCD, 0xCE, 0xCF, 0xCC, 0x60, 0x3A, 0x23, 0x40, 0x27, 0x3D, 0x22,
-    0xD8, 0x61, 0x62, 0x63, 0x64, 0x65, 0x66, 0x67, 0x68, 0x69, 0xAB, 0xBB, 0xF0, 0xFD, 0xFE, 0xB1,
-    0xB0, 0x6A, 0x6B, 0x6C, 0x6D, 0x6E, 0x6F, 0x70, 0x71, 0x72, 0xAA, 0xBA, 0xE6, 0xB8, 0xC6, 0x80,
-    0xB5, 0x7E, 0x73, 0x74, 0x75, 0x76, 0x77, 0x78, 0x79, 0x7A, 0xA1, 0xBF, 0xD0, 0xDD, 0xDE, 0xAE,
-    0x5E, 0xA3, 0xA5, 0xB7, 0xA9, 0xA7, 0xB6, 0xBC, 0xBD, 0xBE, 0x5B, 0x5D, 0xAF, 0xA8, 0xB4, 0xD7,
-    0x7B, 0x41, 0x42, 0x43, 0x44, 0x45, 0x46, 0x47, 0x48, 0x49, 0xAD, 0xF4, 0xF6, 0xF2, 0xF3, 0xF5,
-    0x7D, 0x4A, 0x4B, 0x4C, 0x4D, 0x4E, 0x4F, 0x50, 0x51, 0x52, 0xB9, 0xFB, 0xFC, 0xF9, 0xFA, 0xDF,
-    0x5C, 0xF7, 0x53, 0x54, 0x55, 0x56, 0x57, 0x58, 0x59, 0x5A, 0xB2, 0xD4, 0xD6, 0xD2, 0xD3, 0xD5,
-    0x30, 0x31, 0x32, 0x33, 0x34, 0x35, 0x36, 0x37, 0x38, 0x39, 0xB3, 0xDB, 0xDC, 0xD9, 0xDA, 0xFF,
-    };
-
-// This table is used for converting code page 1252 to the subset of UTF-8 that
-// that contains CP1252
-
-static const unsigned short
-cp1252_to_utf8_values[256] =
-    {
-    0x0000, 0x0001, 0x0002, 0x0003, 0x0004, 0x0005, 0x0006, 0x0007, 0x0008, 0x0009, 0x000a, 0x000b, 0x000c, 0x000d, 0x000e, 0x000f, // 00
-    0x0010, 0x0011, 0x0012, 0x0013, 0x0014, 0x0015, 0x0016, 0x0017, 0x0018, 0x0019, 0x001a, 0x001b, 0x001c, 0x001d, 0x001e, 0x001f, // 10
-    0x0020, 0x0021, 0x0022, 0x0023, 0x0024, 0x0025, 0x0026, 0x0027, 0x0028, 0x0029, 0x002a, 0x002b, 0x002c, 0x002d, 0x002e, 0x002f, // 20
-    0x0030, 0x0031, 0x0032, 0x0033, 0x0034, 0x0035, 0x0036, 0x0037, 0x0038, 0x0039, 0x003a, 0x003b, 0x003c, 0x003d, 0x003e, 0x003f, // 30
-    0x0040, 0x0041, 0x0042, 0x0043, 0x0044, 0x0045, 0x0046, 0x0047, 0x0048, 0x0049, 0x004a, 0x004b, 0x004c, 0x004d, 0x004e, 0x004f, // 40
-    0x0050, 0x0051, 0x0052, 0x0053, 0x0054, 0x0055, 0x0056, 0x0057, 0x0058, 0x0059, 0x005a, 0x005b, 0x005c, 0x005d, 0x005e, 0x005f, // 50
-    0x0060, 0x0061, 0x0062, 0x0063, 0x0064, 0x0065, 0x0066, 0x0067, 0x0068, 0x0069, 0x006a, 0x006b, 0x006c, 0x006d, 0x006e, 0x006f, // 60
-    0x0070, 0x0071, 0x0072, 0x0073, 0x0074, 0x0075, 0x0076, 0x0077, 0x0078, 0x0079, 0x007a, 0x007b, 0x007c, 0x007d, 0x007e, 0x007f, // 70
-    0x20ac, 0x0081, 0x201a, 0x0192, 0x201e, 0x2026, 0x2020, 0x2021, 0x02c6, 0x2030, 0x0160, 0x2039, 0x0152, 0x008d, 0x017d, 0x008f, // 80
-    0x0090, 0x2018, 0x2019, 0x201c, 0x201d, 0x2022, 0x2013, 0x2014, 0x02dc, 0x2122, 0x0161, 0x203a, 0x0153, 0x009d, 0x017e, 0x0178, // 90
-    0x00a0, 0x00a1, 0x00a2, 0x00a3, 0x00a4, 0x00a5, 0x00a6, 0x00a7, 0x00a8, 0x00a9, 0x00aa, 0x00ab, 0x00ac, 0x00ad, 0x00ae, 0x00af, // A0
-    0x00b0, 0x00b1, 0x00b2, 0x00b3, 0x00b4, 0x00b5, 0x00b6, 0x00b7, 0x00b8, 0x00b9, 0x00ba, 0x00bb, 0x00bc, 0x00bd, 0x00be, 0x00bf, // B0
-    0x00c0, 0x00c1, 0x00c2, 0x00c3, 0x00c4, 0x00c5, 0x00c6, 0x00c7, 0x00c8, 0x00c9, 0x00ca, 0x00cb, 0x00cc, 0x00cd, 0x00ce, 0x00cf, // C0
-    0x00d0, 0x00d1, 0x00d2, 0x00d3, 0x00d4, 0x00d5, 0x00d6, 0x00d7, 0x00d8, 0x00d9, 0x00da, 0x00db, 0x00dc, 0x00dd, 0x00de, 0x00df, // D0
-    0x00e0, 0x00e1, 0x00e2, 0x00e3, 0x00e4, 0x00e5, 0x00e6, 0x00e7, 0x00e8, 0x00e9, 0x00ea, 0x00eb, 0x00ec, 0x00ed, 0x00ee, 0x00ef, // E0
-    0x00f0, 0x00f1, 0x00f2, 0x00f3, 0x00f4, 0x00f5, 0x00f6, 0x00f7, 0x00f8, 0x00f9, 0x00fa, 0x00fb, 0x00fc, 0x00fd, 0x00fe, 0x00ff, // F0
-    };
-
-// This map table doe the reverse UTF-8 conversion back to cp1252
-static const std::unordered_map<unsigned short, unsigned char>utf8_to_cp1252_values =
-    {
-    {0x0000, 0x00}, {0x0001, 0x01}, {0x0002, 0x02}, {0x0003, 0x03}, {0x0004, 0x04}, {0x0005, 0x05}, {0x0006, 0x06}, {0x0007, 0x07},
-    {0x0008, 0x08}, {0x0009, 0x09}, {0x000a, 0x0a}, {0x000b, 0x0b}, {0x000c, 0x0c}, {0x000d, 0x0d}, {0x000e, 0x0e}, {0x000f, 0x0f},
-    {0x0010, 0x10}, {0x0011, 0x11}, {0x0012, 0x12}, {0x0013, 0x13}, {0x0014, 0x14}, {0x0015, 0x15}, {0x0016, 0x16}, {0x0017, 0x17},
-    {0x0018, 0x18}, {0x0019, 0x19}, {0x001a, 0x1a}, {0x001b, 0x1b}, {0x001c, 0x1c}, {0x001d, 0x1d}, {0x001e, 0x1e}, {0x001f, 0x1f},
-    {0x0020, 0x20}, {0x0021, 0x21}, {0x0022, 0x22}, {0x0023, 0x23}, {0x0024, 0x24}, {0x0025, 0x25}, {0x0026, 0x26}, {0x0027, 0x27},
-    {0x0028, 0x28}, {0x0029, 0x29}, {0x002a, 0x2a}, {0x002b, 0x2b}, {0x002c, 0x2c}, {0x002d, 0x2d}, {0x002e, 0x2e}, {0x002f, 0x2f},
-    {0x0030, 0x30}, {0x0031, 0x31}, {0x0032, 0x32}, {0x0033, 0x33}, {0x0034, 0x34}, {0x0035, 0x35}, {0x0036, 0x36}, {0x0037, 0x37},
-    {0x0038, 0x38}, {0x0039, 0x39}, {0x003a, 0x3a}, {0x003b, 0x3b}, {0x003c, 0x3c}, {0x003d, 0x3d}, {0x003e, 0x3e}, {0x003f, 0x3f},
-    {0x0040, 0x40}, {0x0041, 0x41}, {0x0042, 0x42}, {0x0043, 0x43}, {0x0044, 0x44}, {0x0045, 0x45}, {0x0046, 0x46}, {0x0047, 0x47},
-    {0x0048, 0x48}, {0x0049, 0x49}, {0x004a, 0x4a}, {0x004b, 0x4b}, {0x004c, 0x4c}, {0x004d, 0x4d}, {0x004e, 0x4e}, {0x004f, 0x4f},
-    {0x0050, 0x50}, {0x0051, 0x51}, {0x0052, 0x52}, {0x0053, 0x53}, {0x0054, 0x54}, {0x0055, 0x55}, {0x0056, 0x56}, {0x0057, 0x57},
-    {0x0058, 0x58}, {0x0059, 0x59}, {0x005a, 0x5a}, {0x005b, 0x5b}, {0x005c, 0x5c}, {0x005d, 0x5d}, {0x005e, 0x5e}, {0x005f, 0x5f},
-    {0x0060, 0x60}, {0x0061, 0x61}, {0x0062, 0x62}, {0x0063, 0x63}, {0x0064, 0x64}, {0x0065, 0x65}, {0x0066, 0x66}, {0x0067, 0x67},
-    {0x0068, 0x68}, {0x0069, 0x69}, {0x006a, 0x6a}, {0x006b, 0x6b}, {0x006c, 0x6c}, {0x006d, 0x6d}, {0x006e, 0x6e}, {0x006f, 0x6f},
-    {0x0070, 0x70}, {0x0071, 0x71}, {0x0072, 0x72}, {0x0073, 0x73}, {0x0074, 0x74}, {0x0075, 0x75}, {0x0076, 0x76}, {0x0077, 0x77},
-    {0x0078, 0x78}, {0x0079, 0x79}, {0x007a, 0x7a}, {0x007b, 0x7b}, {0x007c, 0x7c}, {0x007d, 0x7d}, {0x007e, 0x7e}, {0x007f, 0x7f},
-    {0x20ac, 0x80}, {0x0081, 0x81}, {0x201a, 0x82}, {0x0192, 0x83}, {0x201e, 0x84}, {0x2026, 0x85}, {0x2020, 0x86}, {0x2021, 0x87},
-    {0x02c6, 0x88}, {0x2030, 0x89}, {0x0160, 0x8a}, {0x2039, 0x8b}, {0x0152, 0x8c}, {0x008d, 0x8d}, {0x017d, 0x8e}, {0x008f, 0x8f},
-    {0x0090, 0x90}, {0x2018, 0x91}, {0x2019, 0x92}, {0x201c, 0x93}, {0x201d, 0x94}, {0x2022, 0x95}, {0x2013, 0x96}, {0x2014, 0x97},
-    {0x02dc, 0x98}, {0x2122, 0x99}, {0x0161, 0x9a}, {0x203a, 0x9b}, {0x0153, 0x9c}, {0x009d, 0x9d}, {0x017e, 0x9e}, {0x0178, 0x9f},
-    {0x00a0, 0xa0}, {0x00a1, 0xa1}, {0x00a2, 0xa2}, {0x00a3, 0xa3}, {0x00a4, 0xa4}, {0x00a5, 0xa5}, {0x00a6, 0xa6}, {0x00a7, 0xa7},
-    {0x00a8, 0xa8}, {0x00a9, 0xa9}, {0x00aa, 0xaa}, {0x00ab, 0xab}, {0x00ac, 0xac}, {0x00ad, 0xad}, {0x00ae, 0xae}, {0x00af, 0xaf},
-    {0x00b0, 0xb0}, {0x00b1, 0xb1}, {0x00b2, 0xb2}, {0x00b3, 0xb3}, {0x00b4, 0xb4}, {0x00b5, 0xb5}, {0x00b6, 0xb6}, {0x00b7, 0xb7},
-    {0x00b8, 0xb8}, {0x00b9, 0xb9}, {0x00ba, 0xba}, {0x00bb, 0xbb}, {0x00bc, 0xbc}, {0x00bd, 0xbd}, {0x00be, 0xbe}, {0x00bf, 0xbf},
-    {0x00c0, 0xc0}, {0x00c1, 0xc1}, {0x00c2, 0xc2}, {0x00c3, 0xc3}, {0x00c4, 0xc4}, {0x00c5, 0xc5}, {0x00c6, 0xc6}, {0x00c7, 0xc7},
-    {0x00c8, 0xc8}, {0x00c9, 0xc9}, {0x00ca, 0xca}, {0x00cb, 0xcb}, {0x00cc, 0xcc}, {0x00cd, 0xcd}, {0x00ce, 0xce}, {0x00cf, 0xcf},
-    {0x00d0, 0xd0}, {0x00d1, 0xd1}, {0x00d2, 0xd2}, {0x00d3, 0xd3}, {0x00d4, 0xd4}, {0x00d5, 0xd5}, {0x00d6, 0xd6}, {0x00d7, 0xd7},
-    {0x00d8, 0xd8}, {0x00d9, 0xd9}, {0x00da, 0xda}, {0x00db, 0xdb}, {0x00dc, 0xdc}, {0x00dd, 0xdd}, {0x00de, 0xde}, {0x00df, 0xdf},
-    {0x00e0, 0xe0}, {0x00e1, 0xe1}, {0x00e2, 0xe2}, {0x00e3, 0xe3}, {0x00e4, 0xe4}, {0x00e5, 0xe5}, {0x00e6, 0xe6}, {0x00e7, 0xe7},
-    {0x00e8, 0xe8}, {0x00e9, 0xe9}, {0x00ea, 0xea}, {0x00eb, 0xeb}, {0x00ec, 0xec}, {0x00ed, 0xed}, {0x00ee, 0xee}, {0x00ef, 0xef},
-    {0x00f0, 0xf0}, {0x00f1, 0xf1}, {0x00f2, 0xf2}, {0x00f3, 0xf3}, {0x00f4, 0xf4}, {0x00f5, 0xf5}, {0x00f6, 0xf6}, {0x00f7, 0xf7},
-    {0x00f8, 0xf8}, {0x00f9, 0xf9}, {0x00fa, 0xfa}, {0x00fb, 0xfb}, {0x00fc, 0xfc}, {0x00fd, 0xfd}, {0x00fe, 0xfe}, {0x00ff, 0xff},
-    };
-
-// This function extracts the next unicode code point from a stream of UTF-8
-// data.
-
-static bool
-raw_is_SBC()
-  {
-  bool retval = false;
-  switch(source_codeset)
-    {
-    case cs_cp1252_e:
-      retval = true;
-      break;
-    default:
-      break;
-    }
-  return retval;
-  }
-
-
-static size_t
-extract_next_code_point(const unsigned char *utf8,
-                        const size_t /*length_in_bytes*/,
-                        size_t &position)
-  {
-  long retval = -1; // Means a badly formed code point
-  unsigned char ch = utf8[position++];
-  long under_construction = 0;
-  int countdown = 0;
-  
-  if( (ch & 0x80) == 0x00 )
-    {
-    // We are in the ASCII subset of UTF-8, and we are done
-    retval = ch;
-    goto done;
-    }
-  else if( (ch & 0xE0) == 0xC0 )
-    {
-    // There is one byte to follow
-    countdown = 1;
-    under_construction = ch & 0x1F;
-    }
-  else if( (ch & 0xF0) == 0xE0 )
-    {
-    countdown = 2;
-    under_construction = ch & 0x0F;
-    }
-  else if( (ch & 0xF8) == 0xF0 )
-    {
-    countdown = 3;
-    under_construction = ch & 0x07;
-    }
-  else
-    {
-    // We have a poorly-constructed UTF-8 encoding
-    goto done;
-    }
-  while( countdown-- )
-    {
-    ch = utf8[position++];
-    // We are in a follow-up encoded byte:
-    if( (ch & 0xC0) == 0x80 )
-      {
-      // The top two bits are 10, so build in the bottom six bits
-      under_construction <<= 6;
-      under_construction |= (ch & 0x3F);
-      }
-    else
-      {
-      // This is a poorly-formed encoding
-      goto done;
-      }
-    }
-  retval = under_construction;
-
-  done:
-  return retval;
-  }
-
-void flipper(void)
-    {
-    for(int i=0; i<256; i++)
-        {
-        fprintf(stderr, "{0x%4.4x, 0x%2.2x}, ", cp1252_to_utf8_values[i], i);
-        if( (i % 8) == 7 )
-            {
-            fprintf(stderr, "\n");
-            }
-        }
-    }
-
-extern "C"
-char __gg__ascii_to_ascii_chr(char ch)
-    {
-    return ch;
-    }
-
-extern "C"
-char __gg__ascii_to_ebcdic_chr(char ch)
-    {
-    return (char)__gg__cp1252_to_cp1140_values[(ch&0xFF)];
-    }
-
-extern "C"
-char *
-__gg__raw_to_ascii(char **dest, size_t *dest_size, const char *in, size_t length)
-  {
-  // We are anticipating `length` characters, some of which might be multi-
-  // character UTF-8 codepoints.  We are sending back a nul-terminated string
-  // of SBC ASCII values.
-  
-  __gg__realloc_if_necessary(dest, dest_size, length+1);
-
-  // This is the byte position of the output
-  size_t index = 0;
-
-  // This is the byte position of the input
-  size_t position = 0;
-
-  while( index < length )
-    {
-    // In the case of "display "âêîôû", when the source code is encoded in
-    // UTF-8, the field->data.capacity is showing up as 10, because that 
-    // UTF-8 string is ten bytes long, and the parser is not counting
-    // characters.  The data.initial field is indeed nul-terminated, so when we
-    // hit a nul, we bug out:
-    if( in[position] == '\0' )
-      {
-      // We have hit the end. We want to space-fill to the right:
-      while( index < length )
-        {
-        (*dest)[index++] = internal_space;
-        }
-      break;
-      }
-
-    // Special handling for PIC X VALUE HIGH-VALUE.  If we just hand default
-    // 0xFF values to the rest of the routine, the utf-8 detection will give
-    // us a result that confuses the remainder of the processing.
-    if( (in[position]&0xFF) == 0xFF )
-      {
-      (*dest)[index++] = in[position++];
-      continue;
-      }
-
-    if( raw_is_SBC() )
-      {
-      (*dest)[index++] = in[position++];
-      continue;
-      }
-
-    size_t code_point;
-    // Pull the next code_point from the UTF-8 stream
-    long unicode_point = extract_next_code_point((const unsigned char *)in,
-                                                 length,
-                                                 position );
-
-    // Check for that unicode code point in the subset of characters we
-    // know about:
-    std::unordered_map<unsigned short, unsigned char>::const_iterator it =
-        utf8_to_cp1252_values.find(unicode_point);
-    if( it == utf8_to_cp1252_values.end() )
-        {
-        // That unicode character isn't in our list
-        code_point = ASCII_REPLACEMENT;
-        }
-    else
-        {
-        code_point = it->second;
-        }
-    (*dest)[index++] = (char)code_point;
-    }
-  (*dest)[index++] = '\0';
-
-  return *dest;
-  }
-
-extern "C"
-char *
-__gg__raw_to_ebcdic(char **dest, size_t *dest_size, const char *in, size_t length)
-    {
-    // A UTF-8 string is at least as long as the single-byte-coded resulting
-    // string:
-    __gg__realloc_if_necessary(dest, dest_size, length+1);
-
-    size_t index = 0;
-
-    size_t position = 0;
-    size_t code_point;
-    while( index < length )
-        {
-        // See comments in __gg__raw_to_ascii
-        if( in[position] == '\0' )
-          {
-          // We have hit the end. We want to space-fill to the right:
-          while( index < length )
-            {
-            (*dest)[index++] = internal_space;
-            }
-          break;
-          }
-        if( raw_is_SBC() )
-          {
-          code_point = in[position++];
-          long ebcdic_code_point = __gg__cp1252_to_cp1140_values[code_point&0xFF];
-          (*dest)[index++] = ebcdic_code_point;
-          continue;
-          }
-        if( (in[position]&0xff) == 0xff )
-          {
-          // HIGH-VALUE is a special case 
-          (*dest)[index++] = in[position++];
-          continue;
-          }
-
-        // Pull the next code_point from the UTF-8 stream
-        long unicode_point = extract_next_code_point(   (const unsigned char *)in,
-                                                                length,
-                                                                position );
-        // Check for that unicode code point in the subset of characters we
-        // know about:
-        std::unordered_map<unsigned short, unsigned char>::const_iterator it =
-            utf8_to_cp1252_values.find(unicode_point);
-        if( it == utf8_to_cp1252_values.end() )
-            {
-            // That unicode character isn't in our list
-            code_point = ASCII_REPLACEMENT;
-            }
-        else
-            {
-            code_point = it->second;
-            }
-        // TODO: This could be sped up by creating a utf8_to_cp1140_values map.
-        // But sufficient unto the day are the evils thereof
-        long ebcdic_code_point = __gg__cp1252_to_cp1140_values[code_point&0xFF];
-        (*dest)[index++] = ebcdic_code_point;
-        }
-    (*dest)[index++] = '\0';
-
-    return *dest;
-    }
-
-static
-char *
-convert_cp1252_to_utf8(char **dest, size_t *dest_size, const char *in, size_t length)
-    {
-    // Worst case is all unicode characters.
-    __gg__realloc_if_necessary(dest, dest_size, 4 * length + 1);
-
-    size_t index = 0;
-    for(size_t i=0; i<length; i++)
-        {
-        unsigned char ch = *in++;
-        size_t unicode_point = cp1252_to_utf8_values[ch];
-        if( unicode_point < 0x0080 )
-            {
-            // Single-byte
-            (*dest)[index++] = (char)unicode_point;
-            }
-        else if(unicode_point < 0x0800)
-            {
-            // Two-byte:
-            (*dest)[index++] = 0xC0 + (unicode_point>>6);
-            (*dest)[index++] = 0x80 + ((unicode_point>>0) & 0x3F);
-            }
-        else if(unicode_point < 0x10000)
-            {
-            // Three-byte:
-            (*dest)[index++] = 0xE0 + (unicode_point>>12);
-            (*dest)[index++] = 0x80 + ((unicode_point>>6) & 0x3F);
-            (*dest)[index++] = 0x80 + ((unicode_point>>0) & 0x3F);
-            }
-        else
-            {
-            // Four-byte:
-            (*dest)[index++] = 0xF0 + (unicode_point>>18);
-            (*dest)[index++] = 0x80 + ((unicode_point>>12) & 0x3F);
-            (*dest)[index++] = 0x80 + ((unicode_point>>6)  & 0x3F);
-            (*dest)[index++] = 0x80 + ((unicode_point>>0)  & 0x3F);
-            }
-        }
-    (*dest)[index++] = '\0';
-
-    return *dest;
-    }
-
-// This is the address of the 256-character map for internal characters
-// It'll be set to one-to-one for ASCII, and to cp1252-to-cp1140_values for
-// EBCDIC.
-unsigned short const *__gg__internal_codeset_map;
-
-// Here is the list of function pointers establish which ones of the paired
-// possibilities of conversion routines are actually in use.
-
-char  (*__gg__ascii_to_internal_chr)(char);
-void  (*__gg__ascii_to_internal_str)(char *str, size_t length);
-char *(*__gg__raw_to_internal)(char **dest, size_t *dest_size, const char *in, const size_t length);
-char *(*__gg__internal_to_console_cm)(char **dest, size_t *dest_size, const char *in, size_t length);
-void  (*__gg__console_to_internal_cm)(char * const str, size_t length);
-void  (*__gg__internal_to_ascii)(char *str, size_t length);
-
-extern "C"
-void __gg__set_internal_codeset(int use_ebcdic)
-    {
-    __gg__ebcdic_codeset_in_use = !!use_ebcdic;
-    }
-
-extern "C"
-void __gg__text_conversion_override(text_device_t device,
-                                    text_codeset_t codeset)
-    {
-    // Establish the default sourcecode and console codesets, and
-    // establish the codeset conversion routines:
-
-    if( internal_is_ebcdic )
-        {
-//        fprintf(stderr, "Setting up EBCDIC\n");
-        __gg__internal_codeset_map   =  __gg__cp1252_to_cp1140_values;
-        __gg__ascii_to_internal_chr  = &__gg__ascii_to_ebcdic_chr;
-        __gg__ascii_to_internal_str  = &__gg__ascii_to_ebcdic;
-        __gg__raw_to_internal        = &__gg__raw_to_ebcdic;
-        __gg__internal_to_console_cm = &__gg__ebcdic_to_console;
-        __gg__console_to_internal_cm = &__gg__console_to_ebcdic;
-        __gg__internal_to_ascii      = &__gg__ebcdic_to_ascii;
-        }
-    else
-        {
-//        fprintf(stderr, "Setting up ASCII\n");
-        __gg__internal_codeset_map   =  __gg__one_to_one_values;
-        __gg__ascii_to_internal_chr  = &__gg__ascii_to_ascii_chr;
-        __gg__ascii_to_internal_str  = &__gg__ascii_to_ascii;
-        __gg__raw_to_internal        = &__gg__raw_to_ascii;
-        __gg__internal_to_console_cm = &__gg__ascii_to_console;
-        __gg__console_to_internal_cm = &__gg__console_to_ascii;
-        __gg__internal_to_ascii      = &__gg__ascii_to_ascii;
-        }
-
-    switch(device)
-        {
-        case td_default_e:
-          {
-          // We are setting our codesets to the defaults
-      
-          // First, sort out the console:
-
-          // It is my understanding that the environment variable LANG is
-          // supposed to be set by the terminal to indicate the terminal's
-          // current character set.  Let's use that as the winner, even if
-          // that's not quite the way locale(3) works.
-          const char *envLANG = getenv("LANG");
-          if( !envLANG )
-            {
-            // This is odd.  No "LANG"?
-            envLANG = setlocale(LC_CTYPE, NULL);
-            }
-          if( !envLANG )
-            {
-            // This is even more odd. Pick something as a backup to the backup
-            envLANG = "UTF-8";
-            }
-          if( envLANG )
-            {
-            if( strcasestr(envLANG, "UTF-8") ) 
-              {
-              console_codeset = cs_utf8_e;
-              }
-            else
-              {
-              // If it isn't UTF-8, then figure on it being CP1252 as a 
-              // convenient way of specifying an SBC codeset.
-              console_codeset  = cs_cp1252_e;
-              }
-            }
-          break;
-          }
-
-        case td_sourcecode_e:
-            // Explicitly set the source code codeset:
-            source_codeset = codeset;
-            break;
-
-        case td_console_e:
-            // Explicitly set the console codeset:
-            console_codeset = codeset;
-            break;
-        }
-    }
-
-extern "C"
-void
-__gg__ascii_to_ascii(char *, size_t )
-    {
-    return;
-    }
-
-extern "C"
-void
-__gg__ascii_to_ebcdic(char *str, size_t length)
-    {
-    for(size_t i=0; i<length; i++)
-        {
-        str[i] = __gg__cp1252_to_cp1140_values[str[i]&0xFF];
-        }
-    }
-
-extern "C"
-void
-__gg__ebcdic_to_ascii(char * const str, size_t length)
-    {
-    for(size_t i=0; i<length; i++)
-        {
-        str[i] = __gg__cp1140_to_cp1252_values[str[i]&0xFF];
-        }
-    }
-
-extern "C"
-char *__gg__ascii_to_console( char **dest,
-                              size_t *dest_size,
-                              char const * const str,
-                              const size_t length)
-    {
-    if( console_codeset == cs_utf8_e )
-        {
-        __gg__realloc_if_necessary(dest, dest_size, length);
-        convert_cp1252_to_utf8(dest, dest_size, str, length);
-        }
-    else
-        {
-        __gg__realloc_if_necessary(dest, dest_size, length+1);
-        memcpy(*dest, str, length);
-        (*dest)[length] = '\0';
-        }
-    return *dest;
-    }
-
-extern "C"
-char *__gg__ebcdic_to_console(char **dest,
-                              size_t *dest_size,
-                              char const * const str,
-                              const size_t length)
-    {
-    static size_t ebcdic_size = MINIMUM_ALLOCATION_SIZE;
-    static char *ebcdic = (char *)malloc(ebcdic_size);
-    __gg__realloc_if_necessary(&ebcdic, &ebcdic_size, length);
-
-    memcpy(ebcdic, str, length);
-    __gg__ebcdic_to_ascii(ebcdic, length);
-
-    if( console_codeset == cs_utf8_e )
-        {
-        convert_cp1252_to_utf8(dest, dest_size, ebcdic, length);
-        }
-    else
-        {
-        __gg__realloc_if_necessary(dest, dest_size, length+1);
-        strcpy(*dest, ebcdic);
-        }
-    return *dest;
-    }
-
-extern "C"
-void __gg__console_to_ascii(char * const str, size_t length)
-    {
-    // In-place conversion of ASCII data that might be UTF-8 to CP1252
-    if( console_codeset == cs_cp1252_e )
-        {
-        // It's already what we want it to be
-        return;
-        }
-    char *dest = str;
-
-    size_t position = 0;
-    while( position < length )
-        {
-        size_t code_point;
-        // Pull the next code_point from the UTF-8 stream
-        long unicode_point
-            = extract_next_code_point(    (const unsigned char *)str,
-                                                length,
-                                                position );
-        if( unicode_point == -1 )
-            {
-            // The UTF-8 stream was poorly formed.
-            code_point = ASCII_REPLACEMENT;
-            }
-        else
-            {
-            // Check for that unicode code point in the subset of characters we
-            // know about:
-            std::unordered_map<unsigned short, unsigned char>::const_iterator it
-                = utf8_to_cp1252_values.find(unicode_point);
-            if( it == utf8_to_cp1252_values.end() )
-                {
-                // That unicode character isn't in our list
-                code_point = ASCII_REPLACEMENT;
-                }
-            else
-                {
-                code_point = it->second;
-                }
-            }
-        *dest++ = (char)code_point;
-        }
-    *dest++ = '\0';
-    }
-
-extern "C"
-void
-__gg__console_to_ebcdic(char * const str, size_t length)
-    {
-    char *dest = str;
-
-    size_t position = 0;
-    while( position < length )
-        {
-        size_t code_point;
-        // Pull the next code_point from the UTF-8 stream
-        long unicode_point
-            = extract_next_code_point(    (const unsigned char *)str,
-                                                length,
-                                                position );
-        if( unicode_point == -1 )
-            {
-            // The UTF-8 stream was poorly formed.
-            code_point = ASCII_REPLACEMENT;
-            }
-        else
-            {
-            // Check for that unicode code point in the subset of characters we
-            // know about:
-            std::unordered_map<unsigned short, unsigned char>::const_iterator it
-                = utf8_to_cp1252_values.find(unicode_point);
-            if( it == utf8_to_cp1252_values.end() )
-                {
-                // That unicode character isn't in our list
-                code_point = ASCII_REPLACEMENT;
-                }
-            else
-                {
-                code_point = it->second;
-                }
-            }
-        *dest++ = __gg__cp1252_to_cp1140_values[code_point&0xFF]   ;
-        }
-    *dest++ = '\0';
-    }
-
-extern "C"
-size_t
-_to_ctype(char * const location, size_t length)
-  {
-  // Converts from our internal codeset to the system LC_TYPE codeset
-  const char *fromcode;
-  const char *tocode;
-  if( __gg__ebcdic_codeset_in_use )
-    {
-    fromcode = "CP1140";
-    }
-  else
-    {
-    fromcode = "CP1252";
-    }
-  const char *ctype = setlocale(LC_CTYPE, "");
-  
-  if( strcasestr(ctype, "UTF") )
-    {
-    tocode = "UTF-8";
-    }
-  else
-    {
-    tocode = "CP1252";
-    }
-
-  iconv_t cd = iconv_open(tocode, fromcode);
-  assert( cd != (iconv_t)-1 );
-  
-  static char  *dest      = NULL;
-  static size_t dest_size = 0;
-
-  // create a buffer long enough that iconv() won't fail:
-  __gg__realloc_if_necessary(&dest, &dest_size, 4*length+1);
-  
-  // Set up for the iconv() call:
-  char  *inbuf        = location;
-  size_t inbytesleft  = length;
-  char  *outbuf       = dest;
-  size_t outbytesleft = 2*length+1;
-
-  memset(dest, ' ',  2*length+1);
-  iconv(cd, &inbuf, &inbytesleft, &outbuf, &outbytesleft);
-  memcpy(location, dest, length);
-  return 0;
-  }
-  
-extern "C"
-size_t
-_from_ctype(char * const location, size_t length)
-  {
-  // Converts from our internal codeset to the system LC_TYPE codeset
-  const char *fromcode;
-  const char *tocode;
-  if( __gg__ebcdic_codeset_in_use )
-    {
-    tocode = "CP1140";
-    }
-  else
-    {
-    tocode = "CP1252";
-    }
-  const char *ctype = setlocale(LC_CTYPE, "");
-  
-  if( strcasestr(ctype, "UTF") )
-    {
-    fromcode = "UTF-8";
-    }
-  else
-    {
-    fromcode = "CP1252";
-    }
-
-  iconv_t cd = iconv_open(tocode, fromcode);
-  assert( cd != (iconv_t)-1 );
-  
-  static char  *dest      = NULL;
-  static size_t dest_size = 0;
-
-  // create a buffer long enough that iconv() won't fail:
-  __gg__realloc_if_necessary(&dest, &dest_size, length+1);
-  
-  // Set up for the iconv() call:
-  char  *inbuf        = location;
-  size_t inbytesleft  = length;
-  char  *outbuf       = dest;
-  size_t outbytesleft = length+1;
-
-  memset(dest, internal_space, length+1);
-  ///size_t iret = 
-  iconv(cd, &inbuf, &inbytesleft, &outbuf, &outbytesleft);
-  memcpy(location, dest, length);
-  return 0;
-  }
diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc
index 21f519a38bc6..555527c52052 100644
--- a/gcc/cobol/genapi.cc
+++ b/gcc/cobol/genapi.cc
@@ -3450,13 +3450,6 @@ parser_leave_file()
       TRACE1_END
       }
     }
-  if( file_level == 0 && next_program_is_main )
-    {
-    yyerror(
-         "-main switch says \"%s\" should contain the"
-         " starting program, but none was found", 
-         current_filename.back().c_str());
-    }
   current_filename.pop_back();
   }
 
-- 
GitLab