From 3736a4c8692097d3ca556fd3cf9ec98511e5ee07 Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Fri, 7 Feb 2025 08:42:40 -0500
Subject: [PATCH] Makefile.in notices that MULTISUBDIR=/32 to suppress
 32-builds.

---
 gcc/cobol/ChangeLog    |   5 +
 libgcobol/Makefile.in  |  24 +--
 libgcobol/configure    | 322 ++++++++++++++++++++++++++++++++++-------
 libgcobol/configure.ac |  40 ++---
 4 files changed, 307 insertions(+), 84 deletions(-)

diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog
index 29ec5956bb6c..fe39aee8cb54 100644
--- a/gcc/cobol/ChangeLog
+++ b/gcc/cobol/ChangeLog
@@ -1,6 +1,11 @@
+2025-02-07  Robert Dubner <rdubner@symas.com>
+	* Modified configure.ac and Makefile.in to notices that MULTISUBDIR=/32 to
+	suppress 32-builds.
+
 2025-01-28  Robert Dubner <rdubner@symas.com>
 	* Remove TRACE1 statements from parser_enter_file and parser_leave_file;
 	they are incompatible with COPY statements in the DATA DIVISION.
+
 2025-01-24  Robert Dubner <rdubner@symas.com>
 	* Eliminated missing main() error message; we now rely on linker error
 	* Cleaned up valconv-dupe and charmaps-dupe processing in Make-lang.in
diff --git a/libgcobol/Makefile.in b/libgcobol/Makefile.in
index d52e19d7dd8f..7684d031a6cf 100644
--- a/libgcobol/Makefile.in
+++ b/libgcobol/Makefile.in
@@ -22,7 +22,6 @@
 # This was cribbed from the libchill, libiberty, libstdc++, and
 # libobjc Makefile.in files.  Some of this stuff may be unnecessary.
 
-
 SHELL = @SHELL@
 MAKEOVERRIDES=
 
@@ -92,6 +91,7 @@ ALL_CFLAGS = -I. -I$(srcdir) $(CPPFLAGS) $(DEFS) \
 	$(XCFLAGS) $(CFLAGS) $(WARN_CFLAGS) $(MAX_ERRORS)\
 	-DIN_GCC -DIN_TARGET_LIBS -fno-strict-aliasing -fexceptions
 
+
 # Libtool
 # The following strings describe the version of the COBOL library
 # begin compiled and compatibility issues.
@@ -171,9 +171,18 @@ FLAGS_TO_PASS = \
 	"libsubdir=$(libsubdir)" \
 	"tooldir=$(tooldir)"
 
+ifeq "$(MULTISUBDIR)" "/32"
+# suppress 32-bit builds until such time as the host and target executables
+# no longer require __int128 variables
+$(info Suppressing the 32-bit build because of lack of support for __int128 variables)
+BUILDIT =
+else
+BUILDIT = libgcobol$(libsuffix).la
+endif
+
 # The 'all' rule must be the first one so that it is executed if
 # nothing is specified on the command-line.
-all: libgcobol$(libsuffix).la
+all: $(BUILDIT)
 	: $(MAKE) ; exec $(MULTIDO) $(FLAGS_TO_PASS) multi-do DO=all
 
 .SUFFIXES:
@@ -210,7 +219,6 @@ install-info:
 LTLDFLAGS = $(shell $(SHELL) $(top_srcdir)/../libtool-ldflags $(LDFLAGS))
 
 libgcobol$(libsuffix).la: $(OBJS)
-	@echo OBJS: $(OBJS)
 	$(LIBTOOL_LINK) $(CXX) -o $@ $(OBJS) \
 		-Wc,-shared-libgcc -rpath $(toolexeclibdir) \
 		-version-info $(LIBGCOBOL_VERSION) $(extra_ldflags_libgcobol) \
@@ -234,10 +242,6 @@ AUTOCONF = autoconf
 install: install-libs install-headers
 
 install-libs: installdirs
-	@echo "******************GREAT BALLS OF LIBGCOBOL FIRE****************************"
-	@echo "DESTDIR is $(DESTDIR)"
-	@echo "toolexeclibdir is $(toolexeclibdir)"
-	@echo "******************GREAT BALLS OF LIBGCOBOL DONE****************************"
 	$(SHELL) $(multi_basedir)/mkinstalldirs $(DESTDIR)$(toolexeclibdir)
 	$(LIBTOOL_INSTALL) $(INSTALL) libgcobol$(libsuffix).la $(DESTDIR)$(toolexeclibdir);
 	$(MULTIDO) $(FLAGS_TO_PASS) multi-do DO="$@"
@@ -263,11 +267,9 @@ install-strip:
 	    install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \
 	    "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \
 	fi
-#	echo "*********************************************"
-#	echo "This is a little ham-handed, but I lost interest after a while"
-#	echo $(DESTDIR)$(toolexeclibdir)/libgcobol.so.$(VERSION_SUFFIX)
+#	This is a little ham-handed, but after struggling for a while to
+#	do it "correctly", I lost interest
 	strip -s $(DESTDIR)$(toolexeclibdir)/libgcobol.so.$(VERSION_SUFFIX)
-#	echo "*********************************************"history
 
 mostlyclean:
 	-$(LIBTOOL_CLEAN) rm -f libgcobol$(libsuffix).la *.lo
diff --git a/libgcobol/configure b/libgcobol/configure
index 3003002c7e08..7421842c7275 100755
--- a/libgcobol/configure
+++ b/libgcobol/configure
@@ -635,6 +635,8 @@ OBJC_BOEHM_GC_LIBS
 OBJC_BOEHM_GC_INCLUDES
 OBJC_BOEHM_GC
 OBJC_GCFLAGS
+BUILD_LIBGCOBOL_FALSE
+BUILD_LIBGCOBOL_TRUE
 SET_MAKE
 CPP
 OTOOL64
@@ -754,6 +756,7 @@ with_pic
 enable_fast_install
 with_gnu_ld
 enable_libtool_lock
+enable_darwin_at_rpath
 enable_tls
 enable_gcobol_gc
 with_target_bdw_gc
@@ -1391,6 +1394,9 @@ Optional Features:
   --enable-fast-install[=PKGS]
                           optimize for fast installation [default=yes]
   --disable-libtool-lock  avoid locking (might break parallel builds)
+  --enable-darwin-at-rpath
+                          install libraries with @rpath/library-name, requires
+                          rpaths to be added to executables
   --enable-tls            Use thread-local storage [default=yes]
   --enable-gcobol-gc      enable use of Boehm's garbage collector with the GNU
                           Objective-C runtime
@@ -2341,6 +2347,8 @@ VERSION=4:0:0
 # exported.
 ORIGINAL_LD_FOR_MULTILIBS=$LD
 
+. ${srcdir}/configure.tgt
+
 # -------
 # Options
 # -------
@@ -4741,48 +4749,55 @@ if ${lt_cv_path_NM+:} false; then :
   $as_echo_n "(cached) " >&6
 else
   if test -n "$NM"; then
-  # Let the user override the test.
-  lt_cv_path_NM="$NM"
-else
-  lt_nm_to_check="${ac_tool_prefix}nm"
-  if test -n "$ac_tool_prefix" && test "$build" = "$host"; then
-    lt_nm_to_check="$lt_nm_to_check nm"
-  fi
-  for lt_tmp_nm in $lt_nm_to_check; do
-    lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR
-    for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do
-      IFS="$lt_save_ifs"
-      test -z "$ac_dir" && ac_dir=.
-      tmp_nm="$ac_dir/$lt_tmp_nm"
-      if test -f "$tmp_nm" || test -f "$tmp_nm$ac_exeext" ; then
-	# Check to see if the nm accepts a BSD-compat flag.
-	# Adding the `sed 1q' prevents false positives on HP-UX, which says:
-	#   nm: unknown option "B" ignored
-	# Tru64's nm complains that /dev/null is an invalid object file
-	case `"$tmp_nm" -B /dev/null 2>&1 | sed '1q'` in
-	*/dev/null* | *'Invalid file or object type'*)
-	  lt_cv_path_NM="$tmp_nm -B"
-	  break
-	  ;;
-	*)
-	  case `"$tmp_nm" -p /dev/null 2>&1 | sed '1q'` in
-	  */dev/null*)
-	    lt_cv_path_NM="$tmp_nm -p"
-	    break
-	    ;;
-	  *)
-	    lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but
-	    continue # so that we can try to find one that supports BSD flags
-	    ;;
-	  esac
-	  ;;
-	esac
-      fi
-    done
-    IFS="$lt_save_ifs"
-  done
-  : ${lt_cv_path_NM=no}
-fi
+   # Let the user override the nm to test.
+   lt_nm_to_check="$NM"
+ else
+   lt_nm_to_check="${ac_tool_prefix}nm"
+   if test -n "$ac_tool_prefix" && test "$build" = "$host"; then
+     lt_nm_to_check="$lt_nm_to_check nm"
+   fi
+ fi
+ for lt_tmp_nm in "$lt_nm_to_check"; do
+   lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR
+   for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do
+     IFS="$lt_save_ifs"
+     test -z "$ac_dir" && ac_dir=.
+     # Strip out any user-provided options from the nm to test twice,
+     # the first time to test to see if nm (rather than its options) has
+     # an explicit path, the second time to yield a file which can be
+     # nm'ed itself.
+     tmp_nm_path="`$ECHO "$lt_tmp_nm" | sed 's, -.*$,,'`"
+     case "$tmp_nm_path" in
+     */*|*\\*) tmp_nm="$lt_tmp_nm";;
+     *) tmp_nm="$ac_dir/$lt_tmp_nm";;
+     esac
+     tmp_nm_to_nm="`$ECHO "$tmp_nm" | sed 's, -.*$,,'`"
+     if test -f "$tmp_nm_to_nm" || test -f "$tmp_nm_to_nm$ac_exeext" ; then
+       # Check to see if the nm accepts a BSD-compat flag.
+       # Adding the `sed 1q' prevents false positives on HP-UX, which says:
+       #   nm: unknown option "B" ignored
+       case `"$tmp_nm" -B "$tmp_nm_to_nm" 2>&1 | grep -v '^ *$' | sed '1q'` in
+       *$tmp_nm*) lt_cv_path_NM="$tmp_nm -B"
+	 break
+	 ;;
+       *)
+	 case `"$tmp_nm" -p "$tmp_nm_to_nm" 2>&1 | grep -v '^ *$' | sed '1q'` in
+	 *$tmp_nm*)
+	   lt_cv_path_NM="$tmp_nm -p"
+	   break
+	   ;;
+	 *)
+	   lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but
+	   continue # so that we can try to find one that supports BSD flags
+	   ;;
+	 esac
+	 ;;
+       esac
+     fi
+   done
+   IFS="$lt_save_ifs"
+ done
+ : ${lt_cv_path_NM=no}
 fi
 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_NM" >&5
 $as_echo "$lt_cv_path_NM" >&6; }
@@ -5476,6 +5491,11 @@ sysv4 | sysv4.3*)
 tpf*)
   lt_cv_deplibs_check_method=pass_all
   ;;
+vxworks*)
+  # Assume VxWorks cross toolchains are built on Linux, possibly
+  # as canadian for Windows hosts.
+  lt_cv_deplibs_check_method=pass_all
+  ;;
 esac
 
 fi
@@ -5496,6 +5516,19 @@ test -z "$deplibs_check_method" && deplibs_check_method=unknown
 
 
 
+plugin_option=
+plugin_names="liblto_plugin.so liblto_plugin-0.dll cyglto_plugin-0.dll"
+for plugin in $plugin_names; do
+  plugin_so=`${CC} ${CFLAGS} --print-prog-name $plugin`
+  if test x$plugin_so = x$plugin; then
+    plugin_so=`${CC} ${CFLAGS} --print-file-name $plugin`
+  fi
+  if test x$plugin_so != x$plugin; then
+    plugin_option="--plugin $plugin_so"
+    break
+  fi
+done
+
 if test -n "$ac_tool_prefix"; then
   # Extract the first word of "${ac_tool_prefix}ar", so it can be a program name with args.
 set dummy ${ac_tool_prefix}ar; ac_word=$2
@@ -5589,6 +5622,19 @@ else
 fi
 
 test -z "$AR" && AR=ar
+if test -n "$plugin_option"; then
+  if $AR --help 2>&1 | grep -q "\--plugin"; then
+    touch conftest.c
+    $AR $plugin_option rc conftest.a conftest.c
+    if test "$?" != 0; then
+      { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Failed: $AR $plugin_option rc" >&5
+$as_echo "$as_me: WARNING: Failed: $AR $plugin_option rc" >&2;}
+    else
+      AR="$AR $plugin_option"
+    fi
+    rm -f conftest.*
+  fi
+fi
 test -z "$AR_FLAGS" && AR_FLAGS=cru
 
 
@@ -5793,6 +5839,11 @@ else
 fi
 
 test -z "$RANLIB" && RANLIB=:
+if test -n "$plugin_option" && test "$RANLIB" != ":"; then
+  if $RANLIB --help 2>&1 | grep -q "\--plugin"; then
+    RANLIB="$RANLIB $plugin_option"
+  fi
+fi
 
 
 
@@ -5949,7 +6000,7 @@ osf*)
   symcode='[BCDEGQRST]'
   ;;
 solaris*)
-  symcode='[BDRT]'
+  symcode='[BCDRT]'
   ;;
 sco3.2v5*)
   symcode='[DT]'
@@ -6965,7 +7016,7 @@ $as_echo "$lt_cv_ld_force_load" >&6; }
       # darwin 5.x (macOS 10.1) onwards we only need to adjust when the
       # deployment target is forced to an earlier version.
       case ${MACOSX_DEPLOYMENT_TARGET-UNSET},$host in
-	UNSET,*-darwin[89]*|UNSET,*-darwin[12][0123456789]*)
+	UNSET,*-darwin[89]*|UNSET,*-darwin[12][0-9]*)
 	  ;;
 	10.[012][,.]*)
 	  _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress'
@@ -8942,6 +8993,49 @@ if test -z "$aix_libpath"; then aix_libpath="/usr/lib:/lib"; fi
     darwin* | rhapsody*)
 
 
+
+  # Publish an arg to allow the user to select that Darwin host (and target)
+  # libraries should be given install-names like @rpath/libfoo.dylib.  This
+  # requires that the user of the library then adds an 'rpath' to the DSO that
+  # needs access.
+  # NOTE: there are defaults below, for systems that support rpaths.  The person
+  # configuring can override the defaults for any system version that supports
+  # them - they are, however, forced off for system versions without support.
+  # Check whether --enable-darwin-at-rpath was given.
+if test "${enable_darwin_at_rpath+set}" = set; then :
+  enableval=$enable_darwin_at_rpath; if test "x$enable_darwin_at_rpath" = "xyes"; then
+    # This is not supported before macOS 10.5 / Darwin9.
+    case ${MACOSX_DEPLOYMENT_TARGET-UNSET},$host_os in
+      UNSET,darwin[4-8]*|UNSET,rhapsody*|10.[0-4][,.]*)
+	{ $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Darwin @rpath library names are incompatible with OSX versions earlier than 10.5 (rpaths disabled)" >&5
+$as_echo "$as_me: WARNING: Darwin @rpath library names are incompatible with OSX versions earlier than 10.5 (rpaths disabled)" >&2;}
+	enable_darwin_at_rpath=no
+      ;;
+    esac
+   fi
+else
+  case ${MACOSX_DEPLOYMENT_TARGET-UNSET},$host_os in
+    # As above, before 10.5 / Darwin9 this does not work.
+     UNSET,darwin[4-8]*|UNSET,rhapsody*|10.[0-4][,.]*)
+       enable_darwin_at_rpath=no
+       ;;
+
+    # We cannot build and test reliably on macOS 10.11+ (Darwin15+) without use
+    # of rpaths, since runpaths set via DYLD_LIBRARY_PATH are elided by key
+    # system executables (e.g. /bin/sh).  Force rpaths on for these systems.
+      UNSET,darwin1[5-9]*|UNSET,darwin2*|10.1[1-9][,.]*|1[1-9].*[,.]* )
+      { $as_echo "$as_me:${as_lineno-$LINENO}: @rpath library names are needed on macOS versions later than 10.11 (rpaths have been enabled)" >&5
+$as_echo "$as_me: @rpath library names are needed on macOS versions later than 10.11 (rpaths have been enabled)" >&6;}
+      enable_darwin_at_rpath=yes
+      ;;
+    # NOTE: we are not (yet) doing anything for 10.5 .. 10.10, since they can
+    # work with either DYLD_LIBRARY_PATH or embedded rpaths.
+
+    esac
+
+fi
+
+
   archive_cmds_need_lc=no
   hardcode_direct=no
   hardcode_automatic=yes
@@ -8959,9 +9053,13 @@ if test -z "$aix_libpath"; then aix_libpath="/usr/lib:/lib"; fi
   esac
   if test "$_lt_dar_can_shared" = "yes"; then
     output_verbose_link_cmd=func_echo_all
-    archive_cmds="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring $_lt_dar_single_mod${_lt_dsymutil}"
+    _lt_install_name='\$rpath/\$soname'
+    if test "x$enable_darwin_at_rpath" = "xyes"; then
+      _lt_install_name='@rpath/\$soname'
+    fi
+    archive_cmds="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name ${_lt_install_name} \$verstring ${_lt_dsymutil}"
     module_cmds="\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dsymutil}"
-    archive_expsym_cmds="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring ${_lt_dar_single_mod}${_lt_dar_export_syms}${_lt_dsymutil}"
+    archive_expsym_cmds="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name ${_lt_install_name} \$verstring ${_lt_dar_export_syms}${_lt_dsymutil}"
     module_expsym_cmds="sed -e 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dar_export_syms}${_lt_dsymutil}"
 
   else
@@ -9950,7 +10048,7 @@ haiku*)
   soname_spec='${libname}${release}${shared_ext}$major'
   shlibpath_var=LIBRARY_PATH
   shlibpath_overrides_runpath=yes
-  sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/beos/system/lib'
+  sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/system/lib'
   hardcode_into_libs=yes
   ;;
 
@@ -10313,6 +10411,25 @@ uts4*)
   shlibpath_var=LD_LIBRARY_PATH
   ;;
 
+# Shared libraries for VwWorks, >= 7 only at this stage
+# and (fpic) still incompatible with "large" code models
+# in a few configurations. Only for RTP mode in any case,
+# and upon explicit request at configure time.
+vxworks7*)
+  dynamic_linker=no
+  case ${with_multisubdir}-${enable_shared} in
+    *large*)
+      ;;
+    *mrtp*-yes)
+      version_type=linux
+      need_lib_prefix=no
+      need_version=no
+      library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}'
+      soname_spec='${libname}${release}${shared_ext}$major'
+      dynamic_linker="$host_os module_loader"
+      ;;
+  esac
+  ;;
 *)
   dynamic_linker=no
   ;;
@@ -10769,7 +10886,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 10772 "configure"
+#line 10889 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -10875,7 +10992,7 @@ else
   lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2
   lt_status=$lt_dlunknown
   cat > conftest.$ac_ext <<_LT_EOF
-#line 10878 "configure"
+#line 10995 "configure"
 #include "confdefs.h"
 
 #if HAVE_DLFCN_H
@@ -11291,6 +11408,109 @@ fi
 done
 
 
+# -----------------
+# __int128 support
+# -----------------
+
+{ $as_echo "$as_me:${as_lineno-$LINENO}: checking whether __int128 is supported" >&5
+$as_echo_n "checking whether __int128 is supported... " >&6; }
+if ${libgcobol_cv_have_int128+:} false; then :
+  $as_echo_n "(cached) " >&6
+else
+  if test x$gcc_no_link = xyes; then
+  cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+    __int128 foo (__int128 )
+    {
+    __int128 aaa;
+     return (__int128) aaa;
+    }
+
+    __int128 bar (__int128 )
+    {
+    __int128 aaa;
+     return (__int128) aaa;
+    }
+
+int
+main ()
+{
+
+    foo (1);
+    bar (1);
+
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_compile "$LINENO"; then :
+
+    libgcobol_cv_have_int128=yes
+
+else
+
+    libgcobol_cv_have_int128=no
+
+fi
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
+else
+  if test x$gcc_no_link = xyes; then
+  as_fn_error $? "Link tests are not allowed after GCC_NO_EXECUTABLES." "$LINENO" 5
+fi
+cat confdefs.h - <<_ACEOF >conftest.$ac_ext
+/* end confdefs.h.  */
+
+    __int128 foo (__int128 )
+    {
+    __int128 aaa;
+     return (__int128) aaa;
+    }
+
+    __int128 bar (__int128 )
+    {
+    __int128 aaa;
+     return (__int128) aaa;
+    }
+
+int
+main ()
+{
+
+    foo (1);
+    bar (1);
+
+  ;
+  return 0;
+}
+_ACEOF
+if ac_fn_c_try_link "$LINENO"; then :
+
+    libgcobol_cv_have_int128=yes
+
+else
+
+    libgcobol_cv_have_int128=no
+
+fi
+rm -f core conftest.err conftest.$ac_objext \
+    conftest$ac_exeext conftest.$ac_ext
+fi
+fi
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $libgcobol_cv_have_int128" >&5
+$as_echo "$libgcobol_cv_have_int128" >&6; }
+# The following conditional is useful when this creates a Makefile.am file that
+# is subsequently processed into a Makefile.in file.  At the present time,
+# however the libgcobol build uses a hardcoded Makefile.in file.
+ if test "x$libgcobol_cv_have_int128" = xyes; then
+  BUILD_LIBGCOBOL_TRUE=
+  BUILD_LIBGCOBOL_FALSE='#'
+else
+  BUILD_LIBGCOBOL_TRUE='#'
+  BUILD_LIBGCOBOL_FALSE=
+fi
+
+
 # -----------
 # Miscellanea
 # -----------
@@ -11888,6 +12108,10 @@ if test -z "${MAINTAINER_MODE_TRUE}" && test -z "${MAINTAINER_MODE_FALSE}"; then
   as_fn_error $? "conditional \"MAINTAINER_MODE\" was never defined.
 Usually this means the macro was only invoked conditionally." "$LINENO" 5
 fi
+if test -z "${BUILD_LIBGCOBOL_TRUE}" && test -z "${BUILD_LIBGCOBOL_FALSE}"; then
+  as_fn_error $? "conditional \"BUILD_LIBGCOBOL\" was never defined.
+Usually this means the macro was only invoked conditionally." "$LINENO" 5
+fi
 
 : "${CONFIG_STATUS=./config.status}"
 ac_write_fail=0
diff --git a/libgcobol/configure.ac b/libgcobol/configure.ac
index 08cb50a59361..15c56abcad14 100644
--- a/libgcobol/configure.ac
+++ b/libgcobol/configure.ac
@@ -200,42 +200,34 @@ AC_HEADER_STDC
 AC_CHECK_HEADERS(sched.h)
 
 # -----------------
-# _Float128 support
+# __int128 support
 # -----------------
 
-AC_CACHE_CHECK([whether __float128 is supported], [libgcobol_cv_have_float128],
+AC_CACHE_CHECK([whether __int128 is supported], [libgcobol_cv_have_int128],
   [GCC_TRY_COMPILE_OR_LINK([
-    #if (!defined(_ARCH_PPC)) || defined(__LONG_DOUBLE_IEEE128__)
-    typedef _Complex float __attribute__((mode(TC))) __complex128;
-    #else
-    typedef _Complex float __attribute__((mode(KC))) __complex128;
-    #endif
-
-    __float128 foo (__float128 x)
+    __int128 foo (__int128 )
     {
-
-     __complex128 z1, z2;
-
-     z1 = x;
-     z2 = x / 7.Q;
-     z2 /= z1;
-
-     return (__float128) z2;
+    __int128 aaa;
+     return (__int128) aaa;
     }
 
-    __float128 bar (__float128 x)
+    __int128 bar (__int128 )
     {
-      return x * __builtin_huge_valq ();
+    __int128 aaa;
+     return (__int128) aaa;
     }
   ],[
-    foo (1.2Q);
-    bar (1.2Q);
+    foo (1);
+    bar (1);
   ],[
-    libgcobol_cv_have_float128=yes
+    libgcobol_cv_have_int128=yes
   ],[
-    libgcobol_cv_have_float128=no
+    libgcobol_cv_have_int128=no
 ])])
-AM_CONDITIONAL(BUILD_LIBGCOBOL, [test "x$libgcobol_cv_have_float128" = xyes])
+# The following conditional is useful when this creates a Makefile.am file that
+# is subsequently processed into a Makefile.in file.  At the present time,
+# however the libgcobol build uses a hardcoded Makefile.in file.
+AM_CONDITIONAL(BUILD_LIBGCOBOL, [test "x$libgcobol_cv_have_int128" = xyes])
 
 # -----------
 # Miscellanea
-- 
GitLab