#! /bin/sh #************************************************************************** #* * #* OCaml * #* * #* Xavier Leroy, projet Cristal, INRIA Rocquencourt * #* * #* Copyright 1999 Institut National de Recherche en Informatique et * #* en Automatique. * #* * #* All rights reserved. This file is distributed under the terms of * #* the GNU Lesser General Public License version 2.1, with the * #* special exception on linking described in the file LICENSE. * #* * #************************************************************************** ocamlversion=`head -1 VERSION` echo "Configuring OCaml version $ocamlversion" configure_options="$*" prefix=/usr/local bindir='' target_bindir='' libdir='' mandir='' manext=1 host_type=unknown target_type="" ccoption='' asoption='' asppoption='' cclibs='' curseslibs='' mathlib='-lm' dllib='' x11_include_dir='' x11_lib_dir='' libunwind_include_dir='' libunwind_lib_dir='' libunwind_available=false disable_libunwind=false graph_wanted=yes pthread_wanted=yes dl_defs='' verbose=no with_curses=yes debugruntime=false with_instrumented_runtime=false with_sharedlibs=yes partialld="ld -r" with_debugger=ocamldebugger with_ocamldoc=ocamldoc with_frame_pointers=false with_spacetime=false with_profinfo=false profinfo_width=0 no_naked_pointers=false native_compiler=true TOOLPREF="" with_cfi=true flambda=false safe_string=false afl_instrument=false max_testsuite_dir_retries=0 with_cplugins=true with_fpic=false # Try to turn internationalization off, can cause config.guess to malfunction! unset LANG unset LC_ALL LC_CTYPE LC_COLLATE LC_MESSAGES LC_MONETARY LC_NUMERIC LC_TIME # Turn off some MacOS X debugging stuff, same reason unset RC_TRACE_ARCHIVES RC_TRACE_DYLIBS RC_TRACE_PREBINDING_DISABLED # The inf(), wrn(), err() functions below can be used to provide a consistent # way to notify the user. The notification is always given to the stdout # descriptor. # # Their output is redirected to a file-descriptor "3" which is then redirected # to fd 1 at the level of the whole configure script. This is done to not # conflict with how values are returned from functions in shell script. # Consider the following where "It works!" would be mixed with "42". # do_foo() { # if some_command; then # inf "It works!" # echo "42" # fi # } inf() { printf "%b\n" "$*" 1>&3 } wrn() { printf "[WARNING] %b\n" "$*" 1>&3 } err() { printf "[ERROR!] %b\n" "$*" 1>&3 exit 2 } exec 3>&1 # Parse command-line arguments while : ; do case "$1" in "") break;; -prefix|--prefix) prefix=$2; shift;; -bindir|--bindir) bindir=$2; shift;; -target-bindir|--target-bindir) target_bindir="$2"; shift;; -libdir|--libdir) libdir=$2; shift;; -mandir|--mandir) case "$2" in */man[1-9ln]) mandir=`echo $2 | sed -e 's|^\(.*\)/man.$|\1|'` manext=`echo $2 | sed -e 's/^.*\(.\)$/\1/'`;; *) mandir=$2 manext=1;; esac shift;; -libunwinddir|--libunwinddir) libunwind_include_dir=$2/include; libunwind_lib_dir=$2/lib; shift;; -libunwindlib|--libunwindlib) libunwind_lib_dir=$2; shift;; -libunwindinclude|--libunwindinclude) libunwind_include_dir=$2; shift;; -disable-libunwind|--disable-libunwind) disable_libunwind=true;; -host*|--host*) host_type=$2; shift;; -target*|--target*) target_type=$2; shift;; -cc*) ccoption="$2"; shift;; -as) asoption="$2"; shift;; -aspp) asppoption="$2"; shift;; -lib*) cclibs="$2 $cclibs"; shift;; -no-curses|--no-curses) with_curses=no;; -no-shared-libs|--no-shared-libs) with_sharedlibs=no;; -x11include*|--x11include*) x11_include_dir=$2; shift;; -x11lib*|--x11lib*) x11_lib_dir=$2; shift;; -no-graph|--no-graph) graph_wanted=no;; -with-pthread*|--with-pthread*) ;; # Ignored for backward compatibility -no-pthread*|--no-pthread*) pthread_wanted=no;; -partialld|--partialld) partialld="$2"; shift;; -dldefs*|--dldefs*) dl_defs="$2"; shift;; -dllibs*|--dllibs*) dllib="$2"; shift;; -verbose|--verbose) verbose=yes;; -with-debug-runtime|--with-debug-runtime) debugruntime=true;; -with-instrumented-runtime|--with-instrumented-runtime) with_instrumented_runtime=true;; -no-debugger|--no-debugger) with_debugger="";; -no-ocamldoc|--no-ocamldoc) with_ocamldoc="";; -no-ocamlbuild|--no-ocamlbuild) ;; # ignored for backward compatibility -with-frame-pointers|--with-frame-pointers) with_frame_pointers=true;; -no-naked-pointers|--no-naked-pointers) no_naked_pointers=true;; -spacetime|--spacetime) with_spacetime=true; with_profinfo=true; profinfo_width=26;; -reserved-header-bits|--reserved-header-bits) with_spacetime=false; with_profinfo=true; profinfo_width=$2;shift case $profinfo_width in 0) with_profinfo=false;; [0123456789]);; 1?|2?);; 3[012]);; *) err "--reserved-header-bits argument must be less than 32" esac ;; -no-cfi|--no-cfi) with_cfi=false;; -no-native-compiler|--no-native-compiler) native_compiler=false;; -flambda|--flambda) flambda=true;; -no-cplugins|--no-cplugins) with_cplugins=false;; -fPIC|--fPIC) with_fpic=true;; -safe-string|--safe-string) safe_string=true;; -afl-instrument) afl_instrument=true;; *) if echo "$1" | grep -q -e '^--\?[a-zA-Z0-9-]\+='; then err "configure expects arguments of the form '-prefix /foo/bar'," \ "not '-prefix=/foo/bar' (note the '=')." else err "Unknown option \"$1\"." fi;; esac shift done # Sanity checks case "$prefix" in /*) ;; *) err "The -prefix directory must be absolute.";; esac case "$bindir" in /*) ;; "") ;; '$(PREFIX)/'*) ;; *) err 'The -bindir directory must be absolute or relative to $(PREFIX).';; esac case "$libdir" in /*) ;; "") ;; '$(PREFIX)/'*) ;; *) err 'The -libdir directory must be absolute or relative to $(PREFIX).';; esac case "$mandir" in /*) ;; "") ;; '$(PREFIX)/'*) ;; *) err 'The -mandir directory must be absolute or relative to $(PREFIX).';; esac # Generate the files cd config/auto-aux rm -f s.h m.h Makefile touch s.h m.h Makefile # Write options to Makefile echo "# generated by ./configure $configure_options" >> Makefile echo "CONFIGURE_ARGS=$configure_options" >> Makefile # Where to install echo "PREFIX=$prefix" >> Makefile case "$bindir" in "") echo 'BINDIR=$(PREFIX)/bin' >> Makefile bindir="$prefix/bin";; *) echo "BINDIR=$bindir" >> Makefile;; esac echo 'BYTERUN=$(BINDIR)/ocamlrun' >> Makefile case "$libdir" in "") echo 'LIBDIR=$(PREFIX)/lib/ocaml' >> Makefile libdir="$prefix/lib/ocaml";; *) echo "LIBDIR=$libdir" >> Makefile;; esac echo 'STUBLIBDIR=$(LIBDIR)/stublibs' >> Makefile case "$mandir" in "") echo 'MANDIR=$(PREFIX)/man' >> Makefile mandir="$prefix/man";; *) echo "MANDIR=$mandir" >> Makefile;; esac echo "MANEXT=$manext" >> Makefile # Determine the system type if test "$host_type" = "unknown"; then if host_type=`sh ../gnu/config.guess`; then :; else err "Cannot guess host type. You must specify one with the -host option." fi fi if host=`sh ../gnu/config.sub $host_type`; then :; else err "Please specify the correct host type with the -host option" fi inf "Configuring for host $host ..." if test -n "$target_type"; then target="$target_type" TOOLPREF="${target}-" else target="$host" fi inf "Configuring for target $target ..." if [ x"$host" = x"$target" ]; then cross_compiler=false else cross_compiler=true fi # Do we have gcc? if test -z "$ccoption"; then if sh ./searchpath "${TOOLPREF}gcc"; then cc="${TOOLPREF}gcc" else if $cross_compiler; then err "No cross-compiler found for ${target}.\n" \ "It should be named ${TOOLPREF}gcc and be in the PATH." else cc="cc" fi fi else cc="$ccoption" fi inf "Using compiler $cc." # Determine the C compiler family (GCC, Clang, etc) ccfamily=`$cc -E cckind.c | grep '^[a-z]' | tr -s ' ' '-'` case $? in 0) inf "Compiler family and version: $ccfamily.";; *) err "Unable to preprocess the test program.\n" \ "Make sure the C compiler $cc is properly installed.";; esac # Configure the bytecode compiler # The BYTECC make variable defines which compiler and options to use # to compile C code intended to be used by OCaml bytecode programs. # It is used inside OCaml's build system. # The BYTECODE_C_COMPILER make variable says how the C compiler should be # invoked to process a third-party C source file passed to ocamlc # when no -cc command-line option has been specified. # The BYTECCCOMPOPTS make variable contains options to pass to the C # compiler but only when compiling C files that belong to the OCaml # distribution. # In other words, when ocamlc is called to compile a third-party C # source file, it will _not_ pass these options to the C compiler. # The SHAREDCCCOMPOPTS make variable contains options to use to compile C # source files so that the resulting object files can then be integrated # into shared libraries. It is passed to BYTECC for both C source files # in the OCaml distribution and third-party C source files compiled # with ocamlc. bytecc="$cc" mkexe="\$(BYTECC)" mkexedebugflag="-g" bytecccompopts="" byteccprivatecompopts="" bytecclinkopts="" ostype="Unix" exe="" iflexdir="" SO="so" TOOLCHAIN="cc" # Choose reasonable options based on compiler kind # We select high optimization levels, provided we can turn off: # - strict type-based aliasing analysis (too risky for the OCaml runtime) # - strict no-overflow conditions on signed integer arithmetic # (the OCaml runtime assumes Java-style behavior of signed integer arith.) # Concerning optimization level, -O3 is somewhat risky, so take -O2. # Concerning language version, gnu99 is ISO C99 plus GNU extensions # that are often used in standard headers. Older GCC versions # defaults to gnu89, which is not C99. Clang defaults to gnu99 or # gnu11, which is fine. case "$ocamlversion" in *+dev*) gcc_warnings="-Wall -Werror";; *) gcc_warnings="-Wall";; esac case "$ccfamily" in clang-*) bytecccompopts="-O2 -fno-strict-aliasing -fwrapv"; byteccprivatecompopts="$gcc_warnings";; gcc-[012]-*) # Some versions known to miscompile OCaml, e,g, 2.7.2.1, some 2.96. # Plus: C99 support unknown. err "This version of GCC is too old. Please use GCC version 4.2 or above.";; gcc-3-*|gcc-4-[01]) # No -fwrapv option before GCC 3.4. # Known problems with -fwrapv fixed in 4.2 only. wrn "This version of GCC is rather old. Reducing optimization level." wrn "Consider using GCC version 4.2 or above." bytecccompopts="-std=gnu99 -O"; byteccprivatecompopts="$gcc_warnings";; gcc-4-*) bytecccompopts="-std=gnu99 -O2 -fno-strict-aliasing -fwrapv \ -fno-builtin-memcmp"; byteccprivatecompopts="$gcc_warnings";; gcc-*) bytecccompopts="-O2 -fno-strict-aliasing -fwrapv"; byteccprivatecompopts="$gcc_warnings";; *) bytecccompopts="-O";; esac byteccprivatecompopts="-DCAML_NAME_SPACE $byteccprivatecompopts" # Adjust according to target case "$bytecc,$target" in *,*-*-rhapsody*) bytecccompopts="$bytecccompopts -DSHRINKED_GNUC" mathlib="";; *,*-*-darwin*) mathlib="" mkexe="$mkexe -Wl,-no_compact_unwind" # Tell gcc that we can use 32-bit code addresses for threaded code # unless we are compiled for a shared library (-fPIC option) echo "#ifndef __PIC__" >> m.h echo "# define ARCH_CODE32" >> m.h echo "#endif" >> m.h;; *,*-*-haiku*) # No -lm library mathlib="";; *,*-*-beos*) # No -lm library mathlib="";; *gcc,alpha*-*-osf*) if cc="$bytecc" sh ./hasgot -mieee; then bytecccompopts="-mieee $bytecccompopts"; fi # Put code and static data in lower 4GB bytecclinkopts="-Wl,-T,12000000 -Wl,-D,14000000" # Tell gcc that we can use 32-bit code addresses for threaded code echo "#define ARCH_CODE32" >> m.h;; cc,alpha*-*-osf*) bytecccompopts="-std1 -ieee";; *gcc*,alpha*-*-linux*) if cc="$bytecc" sh ./hasgot -mieee; then bytecccompopts="-mieee $bytecccompopts"; fi;; *,mips-*-irix6*) # Turn off warning "unused library" bytecclinkopts="-n32 -Wl,-woff,84";; *,alpha*-*-unicos*) # For the Cray T3E bytecccompopts="$bytecccompopts -DUMK";; *,powerpc-*-aix*) # Avoid name-space pollution by requiring Unix98-conformant includes bytecccompopts="$bytecccompopts -D_XOPEN_SOURCE=500 -D_ALL_SOURCE";; *,*-*-cygwin*) case $target in i686-*) flavor=cygwin;; x86_64-*) flavor=cygwin64;; *) err "unknown cygwin variant";; esac bytecccompopts="$bytecccompopts -U_WIN32" if test $with_sharedlibs = yes; then flexlink="flexlink -chain $flavor -merge-manifest -stack 16777216" flexdir=`$flexlink -where | tr -d '\015'` if test -z "$flexdir"; then wrn "flexlink not found: native shared libraries won't be available." with_sharedlibs=no else iflexdir="-I\"$flexdir\"" mkexe="$flexlink -exe" mkexedebugflag="-link -g" fi fi if test $with_sharedlibs = no; then mkexe="$mkexe -Wl,--stack,16777216" bytecclinkopts="-Wl,--stack,16777216" fi exe=".exe" ostype="Cygwin";; *,*-*-mingw*) dllccompopt="-DCAML_DLL" if test $with_sharedlibs = yes; then case "$target" in i686-*-*) flexlink_chain="mingw";; x86_64-*-*) flexlink_chain="mingw64";; esac flexlink="flexlink -chain $flexlink_chain -merge-manifest -stack 16777216" flexdir=`$flexlink -where` if test -z "$flexdir"; then wrn "flexlink not found: native shared libraries won't be available." with_sharedlibs=no else iflexdir="-I\"$flexdir\"" mkexe="$flexlink -exe" mkexedebugflag="-link -g" fi fi exe=".exe" ostype="Win32" TOOLCHAIN="mingw" SO="dll" ;; *,x86_64-*-linux*) # Tell gcc that we can use 32-bit code addresses for threaded code # unless we are compiled for a shared library (-fPIC option) echo "#ifndef __PIC__" >> m.h echo "# define ARCH_CODE32" >> m.h echo "#endif" >> m.h;; esac # Configure compiler to use in further tests. cc="$bytecc $bytecclinkopts" export cc cclibs verbose # Check C compiler. cc="$bytecc $bytecccompopts $byteccprivatecompopts $bytecclinkopts" sh ./runtest ansi.c case $? in 0) inf "The C compiler is ISO C99 compliant." ;; 1) wrn "The C compiler is ANSI / ISO C90 compliant, but not ISO C99" \ "compliant.";; 2) err "The C compiler $cc is not ISO C compliant.\n" \ "You need an ISO C99 compiler to build OCaml.";; *) if $cross_compiler; then wrn "Unable to compile the test program.\n" \ "This failure is expected for cross-compilation:\n" \ "we will assume the C compiler is ISO C99-compliant." else err "Unable to compile the test program.\n" \ "Make sure the C compiler $cc is properly installed." fi;; esac # For cross-compilation, we need a host-based ocamlrun and ocamlyacc, # and the user must specify the target BINDIR if $cross_compiler; then if ! sh ./searchpath ocamlrun; then err "Cross-compilation requires an ocaml runtime environment\n" \ "(the ocamlrun binary). Moreover, its version must be the same\n" \ "as the one you're trying to build (`cut -f1 -d+ < ../../VERSION`)." else ocaml_system_version=`ocamlrun -version | sed 's/[^0-9]*\([0-9.]*\).*/\1/'` ocaml_source_version=`sed -n '1 s/\([0-9\.]*\).*/\1/ p' < ../../VERSION` if test x"$ocaml_system_version" != x"$ocaml_source_version"; then err "While you have an ocaml runtime environment, its version\n" \ "($ocaml_system_version) doesn't match the version of these\n" \ "sources ($ocaml_source_version)." else echo "CAMLRUN=`./searchpath -p ocamlrun`" >> Makefile fi fi if ! sh ./searchpath ocamlyacc; then err "Cross-compilation requires an ocamlyacc binary." else ocamlyacc 2>/dev/null if test "$?" -ne 1; then err "While you have an ocamlyacc binary, it cannot be executed" \ "successfully." else echo "CAMLYACC=`./searchpath -p ocamlyacc`" >> Makefile fi fi if [ -z "$target_bindir" ]; then err "Cross-compilation requires -target-bindir." else echo "TARGET_BINDIR=$target_bindir" >> Makefile fi fi # cross-compiler # Check the sizes of data types # OCaml needs a 32 or 64 bit architecture, a 32-bit integer type and # a 64-bit integer type inf "Checking the sizes of integers and pointers..." ret=`sh ./runtest sizes.c` # $1 = sizeof(int) # $2 = sizeof(long) # $3 = sizeof(pointers) # $4 = sizeof(short) # $5 = sizeof(long long) if test "$?" -eq 0; then set $ret case "$3" in 4) inf "OK, this is a regular 32 bit architecture." echo "#undef ARCH_SIXTYFOUR" >> m.h arch64=false;; 8) inf "Wow! A 64 bit architecture!" echo "#define ARCH_SIXTYFOUR" >> m.h arch64=true;; *) err "This architecture seems to be neither 32 bits nor 64 bits.\n" \ "OCaml won't run on this architecture.";; esac else # For cross-compilation, runtest always fails: add special handling. case "$target" in i686-*-mingw*) inf "OK, this is a regular 32 bit architecture." echo "#undef ARCH_SIXTYFOUR" >> m.h set 4 4 4 2 8 arch64=false;; x86_64-*-mingw*) inf "Wow! A 64 bit architecture!" echo "#define ARCH_SIXTYFOUR" >> m.h set 4 4 8 2 8 arch64=true;; *) err "Since datatype sizes cannot be guessed when cross-compiling,\n" \ "a hardcoded list is used but your architecture isn't known yet.\n" \ "You need to determine the sizes yourself.\n" \ "Please submit a bug report in order to expand the list." ;; esac fi if test $1 != 4 && test $2 != 4 && test $4 != 4; then err "Sorry, we can't find a 32-bit integer type\n" \ "(sizeof(short) = $4, sizeof(int) = $1, sizeof(long) = $2)\n" \ "OCaml won't run on this architecture." fi if test $2 != 8 && test $5 != 8; then err "Sorry, we can't find a 64-bit integer type\n" \ "(sizeof(long) = $2, sizeof(long long) = $5)\n" \ "OCaml won't run on this architecture." fi echo "#define SIZEOF_INT $1" >> m.h echo "#define SIZEOF_LONG $2" >> m.h echo "#define SIZEOF_PTR $3" >> m.h echo "#define SIZEOF_SHORT $4" >> m.h echo "#define SIZEOF_LONGLONG $5" >> m.h # Determine endianness sh ./runtest endian.c case $? in 0) inf "This is a big-endian architecture." echo "#define ARCH_BIG_ENDIAN" >> m.h;; 1) inf "This is a little-endian architecture." echo "#undef ARCH_BIG_ENDIAN" >> m.h;; 2) err "This architecture seems to be neither big endian nor little" \ "endian.\n OCaml won't run on this architecture.";; *) case $target in *-*-mingw*) inf "This is a little-endian architecture." echo "#undef ARCH_BIG_ENDIAN" >> m.h;; *) wrn "Something went wrong during endianness determination.\n" \ "You will have to figure out endianness yourself\n" \ "(option ARCH_BIG_ENDIAN in m.h).";; esac;; esac # Determine alignment constraints case "$target" in sparc*-*-*|hppa*-*-*|arm*-*-*|mips*-*-*) # On Sparc V9 with certain versions of gcc, determination of double # alignment is not reliable (PR#1521), hence force it. # Same goes for hppa. # PR#5088 suggests same problem on ARM. # PR#5280 reports same problem on MIPS. # But there's a knack (PR#2572): # if we're in 64-bit mode (sizeof(long) == 8), # we must not doubleword-align floats... if test $2 = 8; then inf "Doubles can be word-aligned." echo "#undef ARCH_ALIGN_DOUBLE" >> m.h else inf "Doubles must be doubleword-aligned." echo "#define ARCH_ALIGN_DOUBLE" >> m.h fi;; *) sh ./runtest dblalign.c case $? in 0) inf "Doubles can be word-aligned." echo "#undef ARCH_ALIGN_DOUBLE" >> m.h;; 1) inf "Doubles must be doubleword-aligned." echo "#define ARCH_ALIGN_DOUBLE" >> m.h;; *) case "$target" in *-*-mingw*) inf "Doubles can be word-aligned." echo "#undef ARCH_ALIGN_DOUBLE" >> m.h;; *) wrn "Something went wrong during alignment determination for" \ "doubles.\n" \ "We will assume alignment constraints over doubles.\n" \ "That's a safe bet: OCaml will work even if\n" \ "this architecture actually has no alignment constraints." echo "#define ARCH_ALIGN_DOUBLE" >> m.h;; esac;; esac;; esac case "$target" in # PR#5088: autodetection is unreliable on ARM. PR#5280: also on MIPS. sparc*-*-*|hppa*-*-*|arm*-*-*|mips*-*-*) if test $2 = 8; then inf "64-bit integers can be word-aligned." echo "#undef ARCH_ALIGN_INT64" >> m.h else inf "64-bit integers must be doubleword-aligned." echo "#define ARCH_ALIGN_INT64" >> m.h fi;; *-*-mingw*) true;; # Nothing is in config/m-nt.h so don't add anything. *) sh ./runtest int64align.c case $? in 0) inf "64-bit integers can be word-aligned." echo "#undef ARCH_ALIGN_INT64" >> m.h;; 1) inf "64-bit integers must be doubleword-aligned." echo "#define ARCH_ALIGN_INT64" >> m.h;; *) wrn "Something went wrong during alignment determination for\n" \ "64-bit integers. I'm going to assume this architecture has\n" \ "alignment constraints. That's a safe bet: OCaml will work\n" \ "even if this architecture has actually no alignment\n" \ "constraints." \ echo "#define ARCH_ALIGN_INT64" >> m.h;; esac esac # Shared library support shared_libraries_supported=false dl_needs_underscore=false sharedcccompopts='' mksharedlib='shared-libs-not-available' byteccrpath='' mksharedlibrpath='' natdynlinkopts="" if test $with_sharedlibs = "yes"; then case "$target" in *-*-cygwin*) mksharedlib="$flexlink" mkmaindll="$flexlink -maindll" shared_libraries_supported=true;; *-*-mingw*) mksharedlib="$flexlink" mkmaindll="$flexlink -maindll" shared_libraries_supported=true;; alpha*-*-osf*) case "$bytecc" in *gcc*) sharedcccompopts="-fPIC" mksharedlib="$bytecc -shared" byteccrpath="-Wl,-rpath," mksharedlibrpath="-Wl,-rpath," shared_libraries_supported=true;; cc*) sharedcccompopts="" mksharedlib="ld -shared -expect_unresolved '*'" byteccrpath="-Wl,-rpath," mksharedlibrpath="-rpath " shared_libraries_supported=true;; esac;; *-*-solaris2*) case "$bytecc" in *gcc*) sharedcccompopts="-fPIC" if sh ./solaris-ld; then mksharedlib="ld -G" byteccrpath="-R" mksharedlibrpath="-R" else mksharedlib="$bytecc -shared" bytecclinkopts="$bytecclinkopts -Wl,-E" natdynlinkopts="-Wl,-E" byteccrpath="-Wl,-rpath," mksharedlibrpath="-Wl,-rpath," fi shared_libraries_supported=true;; *) sharedcccompopts="-KPIC" byteccrpath="-R" mksharedlibrpath="-R" mksharedlib="/usr/ccs/bin/ld -G" shared_libraries_supported=true;; esac;; mips*-*-irix[56]*) case "$bytecc" in cc*) sharedcccompopts="";; *gcc*) sharedcccompopts="-fPIC";; esac mksharedlib="ld -shared -rdata_shared" byteccrpath="-Wl,-rpath," mksharedlibrpath="-rpath " shared_libraries_supported=true;; i[3456]86-*-darwin[89].*) mksharedlib="$bytecc -shared -flat_namespace -undefined suppress \ -read_only_relocs suppress" bytecccompopts="$dl_defs $bytecccompopts" dl_needs_underscore=false shared_libraries_supported=true;; *-apple-darwin*) mksharedlib="$bytecc -shared -flat_namespace -undefined suppress \ -Wl,-no_compact_unwind" bytecccompopts="$dl_defs $bytecccompopts" dl_needs_underscore=false shared_libraries_supported=true;; *-*-linux*|*-*-freebsd[3-9]*|*-*-freebsd[1-9][0-9]*\ |*-*-openbsd*|*-*-netbsd*|*-*-dragonfly*|*-*-gnu*|*-*-haiku*) sharedcccompopts="-fPIC" mksharedlib="$bytecc -shared" bytecclinkopts="$bytecclinkopts -Wl,-E" byteccrpath="-Wl,-rpath," mksharedlibrpath="-Wl,-rpath," natdynlinkopts="-Wl,-E" shared_libraries_supported=true;; esac fi if test -z "$mkmaindll"; then mkmaindll=$mksharedlib fi # Configure native dynlink natdynlink=false if test $with_sharedlibs = "yes"; then case "$target" in *-*-cygwin*) natdynlink=true;; *-*-mingw*) natdynlink=true;; i[3456]86-*-linux*) natdynlink=true;; i[3456]86-*-gnu*) natdynlink=true;; x86_64-*-linux*) natdynlink=true;; i[3456]86-*-darwin[89].*) natdynlink=true;; i[3456]86-*-darwin*) if test $arch64 == true; then natdynlink=true fi;; x86_64-*-darwin*) natdynlink=true;; s390x*-*-linux*) natdynlink=true;; powerpc*-*-linux*) natdynlink=true;; sparc*-*-linux*) natdynlink=true;; i686-*-kfreebsd*) natdynlink=true;; x86_64-*-kfreebsd*) natdynlink=true;; x86_64-*-dragonfly*) natdynlink=true;; i[3456]86-*-freebsd*) natdynlink=true;; x86_64-*-freebsd*) natdynlink=true;; i[3456]86-*-openbsd*) natdynlink=true;; x86_64-*-openbsd*) natdynlink=true;; i[3456]86-*-netbsd*) natdynlink=true;; x86_64-*-netbsd*) natdynlink=true;; i386-*-gnu0.3) natdynlink=true;; i[3456]86-*-haiku*) natdynlink=true;; arm*-*-linux*) natdynlink=true;; arm*-*-freebsd*) natdynlink=true;; earm*-*-netbsd*) natdynlink=true;; aarch64-*-linux*) natdynlink=true;; esac fi if test $natdynlink = "true"; then cmxs="cmxs" else cmxs="cmxa" fi # Configure the native-code compiler # The NATIVECC make variable defines which compiler and options to use # to compile C code intended to be used by OCaml native programs. # It is used inside OCaml's build system. # The NATIVE_C_COMPILER make variable says how the C compiler should be # invoked to process a third-party C source file passed to ocamlopt # when no -cc command-line option has been specified. # The NATIVECCCOMPOPTS make variable contains options to pass to the C # compiler, but only when compiling C files that belong to the OCaml # distribution. # In other words, when ocamlopt is called to compile a third-party C # source file, it will _not_ pass these options to the C compiler. arch=none model=default system=unknown case "$target" in sparc*-*-solaris2.*) arch=sparc; system=solaris;; sparc*-*-*bsd*) arch=sparc; system=bsd;; sparc*-*-linux*) arch=sparc; system=linux;; sparc*-*-gnu*) arch=sparc; system=gnu;; i[3456]86-*-linux*) arch=i386; system=linux_`sh ./runtest elf.c`;; i[3456]86-*-*bsd*) arch=i386; system=bsd_`sh ./runtest elf.c`;; i[3456]86-*-solaris*) if $arch64; then arch=amd64; system=solaris else arch=i386; system=solaris fi;; i[3456]86-*-haiku*) arch=i386; system=beos;; i[3456]86-*-beos*) arch=i386; system=beos;; i[3456]86-*-cygwin*) arch=i386; system=cygwin;; i[3456]86-*-darwin*) if $arch64; then arch=amd64; system=macosx else arch=i386; system=macosx fi;; i[3456]86-*-gnu*) arch=i386; system=gnu;; i[3456]86-*-mingw*) arch=i386; system=mingw;; powerpc64le*-*-linux*) arch=power; model=ppc64le; system=elf;; powerpc*-*-linux*) arch=power; if $arch64; then model=ppc64; else model=ppc; fi system=elf;; powerpc-*-netbsd*) arch=power; model=ppc; system=elf;; powerpc-*-openbsd*) arch=power; model=ppc; system=bsd_elf;; s390x*-*-linux*) arch=s390x; model=z10; system=elf;; armv6*-*-linux-gnueabihf) arch=arm; model=armv6; system=linux_eabihf;; arm*-*-linux-gnueabihf) arch=arm; system=linux_eabihf;; armv7*-*-linux-gnueabi) arch=arm; model=armv7; system=linux_eabi;; armv6t2*-*-linux-gnueabi) arch=arm; model=armv6t2; system=linux_eabi;; armv6*-*-linux-gnueabi) arch=arm; model=armv6; system=linux_eabi;; armv6*-*-freebsd*) arch=arm; model=armv6; system=freebsd;; earmv6*-*-netbsd*) arch=arm; model=armv6; system=netbsd;; earmv7*-*-netbsd*) arch=arm; model=armv7; system=netbsd;; armv5te*-*-linux-gnueabi) arch=arm; model=armv5te; system=linux_eabi;; armv5*-*-linux-gnueabi) arch=arm; model=armv5; system=linux_eabi;; arm*-*-linux-gnueabi) arch=arm; system=linux_eabi;; arm*-*-openbsd*) arch=arm; system=bsd;; zaurus*-*-openbsd*) arch=arm; system=bsd;; x86_64-*-linux*) arch=amd64; system=linux;; x86_64-*-gnu*) arch=amd64; system=gnu;; x86_64-*-dragonfly*) arch=amd64; system=dragonfly;; x86_64-*-freebsd*) arch=amd64; system=freebsd;; x86_64-*-netbsd*) arch=amd64; system=netbsd;; x86_64-*-openbsd*) arch=amd64; system=openbsd;; x86_64-*-darwin*) arch=amd64; system=macosx;; x86_64-*-mingw*) arch=amd64; system=mingw;; aarch64-*-linux*) arch=arm64; system=linux;; x86_64-*-cygwin*) arch=amd64; system=cygwin;; esac # Some platforms exist both in 32-bit and 64-bit variants, not distinguished # by $target. Turn off native code compilation on platforms where 64-bit mode # is not supported (PR#4441). # Sometimes, it's 32-bit mode that is not supported (PR#6722). case "$arch64,$arch,$model" in true,sparc,*|true,power,ppc|false,amd64,*) arch=none; model=default; system=unknown;; esac case "$native_compiler" in true) ;; false) arch=none; model=default; system=unknown; natdynlink=false;; esac if test -z "$ccoption"; then nativecc="$bytecc" else nativecc="$ccoption" fi nativecccompopts="$bytecccompopts" nativeccprivatecompopts="$byteccprivatecompopts" nativeccprofopts='' nativecclinkopts='' # FIXME the naming of nativecclinkopts is broken: these are options for # ld (for shared libs), not for cc nativeccrpath="$byteccrpath" case "$arch,$nativecc,$system,$model" in *,*,rhapsody,*) if $arch64; then partialld="ld -r -arch ppc64"; fi;; amd64,gcc*,macosx,*) partialld="ld -r -arch x86_64";; amd64,gcc*,solaris,*) partialld="ld -r -m elf_x86_64";; power,gcc*,elf,ppc) partialld="ld -r -m elf32ppclinux";; power,gcc*,elf,ppc64) partialld="ld -r -m elf64ppc";; power,gcc*,elf,ppc64le) partialld="ld -r -m elf64lppc";; esac asppprofflags='-DPROFILING' case "$arch,$system" in amd64,macosx) if sh ./searchpath clang; then as='clang -arch x86_64 -c' aspp='clang -arch x86_64 -c' else as="${TOOLPREF}as -arch x86_64" aspp="${TOOLPREF}gcc -arch x86_64 -c" fi;; amd64,solaris) as="${TOOLPREF}as --64" aspp="${TOOLPREF}gcc -m64 -c";; i386,solaris) as="${TOOLPREF}as" aspp="${TOOLPREF}gcc -c";; power,elf) if $arch64; then as="${TOOLPREF}as -a64 -mppc64" aspp="${TOOLPREF}gcc -m64 -c" else as="${TOOLPREF}as -mppc" aspp="${TOOLPREF}gcc -m32 -c" fi;; s390x,elf) as="${TOOLPREF}as -m 64 -march=$model" aspp="${TOOLPREF}gcc -c -Wa,-march=$model";; sparc,solaris) as="${TOOLPREF}as" case "$cc" in *gcc*) aspp="${TOOLPREF}gcc -c";; *) aspp="${TOOLPREF}as -P";; esac;; arm,freebsd) as="${TOOLPREF}cc -c" aspp="${TOOLPREF}cc -c";; *,dragonfly) as="${TOOLPREF}as" aspp="${TOOLPREF}cc -c";; *,freebsd) as="${TOOLPREF}as" aspp="${TOOLPREF}cc -c";; amd64,*|arm,*|arm64,*|i386,*|power,bsd*|sparc,*) as="${TOOLPREF}as" case "$ccfamily" in clang-*) aspp="${TOOLPREF}clang -c" ;; *) aspp="${TOOLPREF}gcc -c" ;; esac;; esac if test -n "$asoption"; then as="$asoption"; fi if test -n "$asppoption"; then aspp="$asppoption"; fi cc_profile='-pg' case "$arch,$system" in i386,linux_elf) profiling='true';; i386,gnu) profiling='true';; i386,bsd_elf) profiling='true';; amd64,macosx) profiling='true';; i386,macosx) profiling='true';; sparc,bsd) profiling='true';; sparc,solaris) profiling='true' case "$nativecc" in gcc*) ;; *) cc_profile='-xpg';; esac;; amd64,linux) profiling='true';; amd64,openbsd) profiling='true';; amd64,freebsd) profiling='true';; amd64,netbsd) profiling='true';; arm,netbsd) profiling='true';; amd64,gnu) profiling='true';; arm,linux*) profiling='true';; power,elf) profiling='true';; power,bsd*) profiling='true';; *) profiling='false';; esac # Where is ranlib? if sh ./searchpath ${TOOLPREF}ranlib; then inf "ranlib found" echo "RANLIB=${TOOLPREF}ranlib" >> Makefile echo "RANLIBCMD=${TOOLPREF}ranlib" >> Makefile else inf "ranlib not used" echo "RANLIB=${TOOLPREF}ar rs" >> Makefile echo "RANLIBCMD=" >> Makefile fi echo "ARCMD=${TOOLPREF}ar" >> Makefile # Write the OS type (Unix or Cygwin) echo "#define OCAML_OS_TYPE \"$ostype\"" >> s.h echo "#define OCAML_STDLIB_DIR \"$libdir\"" >> s.h # Do #! scripts work? printf "#!%s\nexit 1\n" `command -v cat` > hashbang4 chmod +x hashbang4 if ( (./hashbang || ./hashbang2 || ./hashbang3 || ./hashbang4) >/dev/null); then inf "#! appears to work in shell scripts." case "$target" in *-*-sunos*|*-*-unicos*) wrn "We won't use it, though, because under SunOS and Unicos it breaks " \ "on pathnames longer than 30 characters" echo "HASHBANGSCRIPTS=false" >> Makefile;; *-*-cygwin*) wrn "We won't use it, though, because of conflicts with .exe extension " \ "under Cygwin" echo "HASHBANGSCRIPTS=false" >> Makefile;; *-*-mingw*) inf "We won't use it, though, because it's on the target platform " \ "it would be used and windows doesn't support it." echo "HASHBANGSCRIPTS=false" >> Makefile;; *) echo "HASHBANGSCRIPTS=true" >> Makefile;; esac else inf "No support for #! in shell scripts" echo "HASHBANGSCRIPTS=false" >> Makefile fi # Use 64-bit file offset if possible bytecccompopts="$bytecccompopts -D_FILE_OFFSET_BITS=64" nativecccompopts="$nativecccompopts -D_FILE_OFFSET_BITS=64" # Check the semantics of signal handlers if sh ./hasgot sigaction sigprocmask; then inf "POSIX signal handling found." echo "#define POSIX_SIGNALS" >> s.h else if sh ./runtest signals.c; then inf "Signals have the BSD semantics." echo "#define BSD_SIGNALS" >> s.h else inf "Signals have the System V semantics." fi if sh ./hasgot sigsetmask; then inf "sigsetmask() found" echo "#define HAS_SIGSETMASK" >> s.h fi fi # For the Pervasives module if sh ./hasgot2 -i math.h $mathlib expm1 log1p hypot copysign; then inf "expm1(), log1p(), hypot(), copysign() found." echo "#define HAS_C99_FLOAT_OPS" >> s.h fi # For the Sys module if sh ./hasgot getrusage; then inf "getrusage() found." echo "#define HAS_GETRUSAGE" >> s.h fi if sh ./hasgot times; then inf "times() found." echo "#define HAS_TIMES" >> s.h fi # For the terminfo module if test "$with_curses" = "yes"; then for libs in "" "-lcurses" "-ltermcap" "-lcurses -ltermcap" "-lncurses"; do if sh ./hasgot $libs tgetent tgetstr tgetnum tputs; then inf "termcap functions found (with libraries '$libs')" echo "#define HAS_TERMCAP" >> s.h curseslibs="${libs}" break fi done fi # For instrumented runtime # (clock_gettime needs -lrt for glibc before 2.17) if $with_instrumented_runtime; then with_instrumented_runtime=false #enabled it only if found for libs in "" "-lrt"; do if sh ./hasgot $libs clock_gettime; then inf "clock_gettime functions found (with libraries '$libs')" instrumented_runtime_libs="${libs}" with_instrumented_runtime=true; break fi done if ! $with_instrumented_runtime; then err "clock_gettime functions not found. " \ "Instrumented runtime can't be built." fi fi # Configuration for the libraries case "$system" in mingw) unix_or_win32="win32"; unixlib="win32unix"; graphlib="win32graph";; *) unix_or_win32="unix"; unixlib="unix"; graphlib="graph";; esac echo "UNIX_OR_WIN32=$unix_or_win32" >> Makefile echo "UNIXLIB=$unixlib" >> Makefile echo "GRAPHLIB=$graphlib" >> Makefile otherlibraries="$unixlib str num dynlink bigarray" # Spacetime profiling is only available for native code on 64-bit targets. case "$native_compiler" in true) if $arch64; then otherlibraries="$otherlibraries raw_spacetime_lib" fi ;; *) ;; esac # For the Unix library has_sockets=no if sh ./hasgot socket socketpair bind listen accept connect; then inf "You have BSD sockets." echo "#define HAS_SOCKETS" >> s.h has_sockets=yes elif sh ./hasgot -lnsl -lsocket socket socketpair bind listen accept connect then inf "You have BSD sockets (with libraries '-lnsl -lsocket')" cclibs="$cclibs -lnsl -lsocket" echo "#define HAS_SOCKETS" >> s.h has_sockets=yes elif sh ./hasgot -lnetwork socket socketpair bind listen accept connect; then echo "You have BSD sockets (with library '-lnetwork')" cclibs="$cclibs -lnetwork" echo "#define HAS_SOCKETS" >> s.h has_sockets=yes else case "$target" in *-*-mingw*) inf "You have BSD sockets (with libraries '-lws2_32')" cclibs="$cclibs -lws2_32" echo "#define HAS_SOCKETS" >> s.h has_sockets=yes ;; *) ;; esac fi if sh ./hasgot -i sys/socket.h -t socklen_t; then inf "socklen_t is defined in " echo "#define HAS_SOCKLEN_T" >> s.h fi if sh ./hasgot inet_aton; then inf "inet_aton() found." echo "#define HAS_INET_ATON" >> s.h fi if sh ./hasgot -i sys/types.h -i sys/socket.h -i netinet/in.h \ -t 'struct sockaddr_in6' \ && sh ./hasgot getaddrinfo getnameinfo inet_pton inet_ntop; then inf "IPv6 is supported." echo "#define HAS_IPV6" >> s.h fi if sh ./hasgot -i stdint.h; then inf "stdint.h found." echo "#define HAS_STDINT_H" >> s.h fi if sh ./hasgot -i unistd.h; then inf "unistd.h found." echo "#define HAS_UNISTD" >> s.h fi if sh ./hasgot -i sys/types.h -t off_t; then inf "off_t is defined in " echo "#define HAS_OFF_T" >> s.h fi if sh ./hasgot -i sys/types.h -i dirent.h; then inf "dirent.h found." echo "#define HAS_DIRENT" >> s.h fi if sh ./hasgot rewinddir; then inf "rewinddir() found." echo "#define HAS_REWINDDIR" >> s.h fi if sh ./hasgot lockf; then inf "lockf() found." echo "#define HAS_LOCKF" >> s.h fi if sh ./hasgot mkfifo; then inf "mkfifo() found." echo "#define HAS_MKFIFO" >> s.h fi if sh ./hasgot getcwd; then inf "getcwd() found." echo "#define HAS_GETCWD" >> s.h fi if sh ./hasgot getwd; then inf "getwd() found." echo "#define HAS_GETWD" >> s.h fi if sh ./hasgot getpriority setpriority; then inf "getpriority() found." echo "#define HAS_GETPRIORITY" >> s.h fi if sh ./hasgot -i sys/types.h -i utime.h && sh ./hasgot utime; then inf "utime() found." echo "#define HAS_UTIME" >> s.h fi if sh ./hasgot utimes; then inf "utimes() found." echo "#define HAS_UTIMES" >> s.h fi if sh ./hasgot dup2; then inf "dup2() found." echo "#define HAS_DUP2" >> s.h fi if sh ./hasgot fchmod fchown; then inf "fchmod() found." echo "#define HAS_FCHMOD" >> s.h fi if sh ./hasgot truncate ftruncate; then inf "truncate() found." echo "#define HAS_TRUNCATE" >> s.h fi select_include='' if sh ./hasgot -i sys/types.h -i sys/select.h; then inf "sys/select.h found." echo "#define HAS_SYS_SELECT_H" >> s.h select_include='-i sys/select.h' fi has_select=no if sh ./hasgot select && \ sh ./hasgot -i sys/types.h $select_include -t fd_set ; then inf "select() found." echo "#define HAS_SELECT" >> s.h has_select=yes fi if sh ./hasgot nanosleep ; then inf "nanosleep() found." echo "#define HAS_NANOSLEEP" >> s.h fi if sh ./hasgot symlink readlink lstat; then inf "symlink() found." echo "#define HAS_SYMLINK" >> s.h fi has_wait=no if sh ./hasgot waitpid; then inf "waitpid() found." echo "#define HAS_WAITPID" >> s.h has_wait=yes fi if sh ./hasgot wait4; then inf "wait4() found." echo "#define HAS_WAIT4" >> s.h has_wait=yes fi if sh ./hasgot -i limits.h && sh ./runtest getgroups.c; then inf "getgroups() found." echo "#define HAS_GETGROUPS" >> s.h fi if sh ./hasgot -i limits.h -i grp.h && sh ./runtest setgroups.c; then inf "setgroups() found." echo "#define HAS_SETGROUPS" >> s.h fi if sh ./hasgot -i limits.h -i grp.h && sh ./runtest initgroups.c; then inf "initgroups() found." echo "#define HAS_INITGROUPS" >> s.h fi if sh ./hasgot -i termios.h && sh ./hasgot tcgetattr tcsetattr tcsendbreak tcflush tcflow; then inf "POSIX termios found." echo "#define HAS_TERMIOS" >> s.h fi if sh ./runtest async_io.c; then inf "Asynchronous I/O are supported." echo "#define HAS_ASYNC_IO" >> s.h fi has_setitimer=no if sh ./hasgot setitimer; then inf "setitimer() found." echo "#define HAS_SETITIMER" >> s.h has_setitimer="yes" fi if sh ./hasgot gethostname; then inf "gethostname() found." echo "#define HAS_GETHOSTNAME" >> s.h fi if sh ./hasgot -i sys/utsname.h && sh ./hasgot uname; then inf "uname() found." echo "#define HAS_UNAME" >> s.h fi has_gettimeofday=no if sh ./hasgot gettimeofday; then inf "gettimeofday() found." echo "#define HAS_GETTIMEOFDAY" >> s.h has_gettimeofday="yes" fi if sh ./hasgot mktime; then inf "mktime() found." echo "#define HAS_MKTIME" >> s.h fi case "$target" in *-*-cygwin*) ;; # setsid emulation under Cygwin breaks the debugger *) if sh ./hasgot setsid; then inf "setsid() found." echo "#define HAS_SETSID" >> s.h fi;; esac if sh ./hasgot putenv; then inf "putenv() found." echo "#define HAS_PUTENV" >> s.h fi if sh ./hasgot -i locale.h && sh ./hasgot setlocale; then inf "setlocale() and found." echo "#define HAS_LOCALE" >> s.h fi if sh ./hasgot $dllib dlopen; then inf "dlopen() found." elif sh ./hasgot $dllib -ldl dlopen; then inf "dlopen() found in -ldl." dllib="$dllib -ldl" else case "$target" in *-*-mingw*) ;; *) shared_libraries_supported=false esac fi if $shared_libraries_supported; then inf "Dynamic loading of shared libraries is supported." echo "#define SUPPORT_DYNAMIC_LINKING" >> s.h if $dl_needs_underscore; then echo '#define DL_NEEDS_UNDERSCORE' >>s.h fi fi if sh ./hasgot -i sys/types.h -i sys/mman.h && sh ./hasgot mmap munmap; then inf "mmap() found." echo "#define HAS_MMAP" >> s.h fi if sh ./hasgot pwrite; then inf "pwrite() found" echo "#define HAS_PWRITE" >> s.h fi nanosecond_stat=none for i in 1 2 3; do if sh ./trycompile -DHAS_NANOSECOND_STAT=$i nanosecond_stat.c; then nanosecond_stat=$i; break fi done if test $nanosecond_stat != "none"; then inf "stat() supports nanosecond precision." echo "#define HAS_NANOSECOND_STAT $nanosecond_stat" >> s.h fi nargs=none for i in 5 6; do if sh ./trycompile -DSYS_${system} -DNUM_ARGS=${i} gethostbyname.c; then nargs=$i; break; fi done if test $nargs != "none"; then inf "gethostbyname_r() found (with ${nargs} arguments)." echo "#define HAS_GETHOSTBYNAME_R $nargs" >> s.h fi nargs=none for i in 7 8; do if sh ./trycompile -DSYS_${system} -DNUM_ARGS=${i} gethostbyaddr.c; then nargs=$i; break; fi done if test $nargs != "none"; then inf "gethostbyaddr_r() found (with ${nargs} arguments)." echo "#define HAS_GETHOSTBYADDR_R $nargs" >> s.h fi if sh ./hasgot mkstemp; then inf "mkstemp() found" echo "#define HAS_MKSTEMP" >> s.h fi if sh ./hasgot nice; then inf "nice() found" echo "#define HAS_NICE" >> s.h fi if sh ./hasgot dup3; then inf "dup3() found" echo "#define HAS_DUP3" >> s.h fi if sh ./hasgot pipe2; then inf "pipe2() found" echo "#define HAS_PIPE2" >> s.h fi if sh ./hasgot accept4; then inf "accept4() found" echo "#define HAS_ACCEPT4" >> s.h fi # Determine if the debugger is supported if test -n "$with_debugger"; then if test "$has_sockets" = "yes"; then inf "Replay debugger supported." with_debugger="ocamldebugger" else inf "No replay debugger (missing system calls)" with_debugger="" fi fi # Determine if system stack overflows can be detected case "$arch,$system" in i386,linux_elf|amd64,linux|power,rhapsody|amd64,macosx|i386,macosx \ |amd64,openbsd|i386,bsd_elf) inf "System stack overflow can be detected." echo "#define HAS_STACK_OVERFLOW_DETECTION" >> s.h;; *) inf "Cannot detect system stack overflow.";; esac # Determine the target architecture for the "num" library case "$arch" in i386) bng_arch=ia32 if sh ./trycompile ia32sse2.c then bng_asm_level=2 else bng_asm_level=1 fi;; power) bng_arch=ppc; bng_asm_level=1;; amd64) bng_arch=amd64; bng_asm_level=1;; arm64) bng_arch=arm64; bng_asm_level=1;; *) bng_arch=generic; bng_asm_level=0;; esac echo "BNG_ARCH=$bng_arch" >> Makefile echo "BNG_ASM_LEVEL=$bng_asm_level" >> Makefile # Determine if the POSIX threads library is supported systhread_support=false if test "$pthread_wanted" = "yes"; then case "$target" in *-*-solaris*) pthread_link="-lpthread -lposix4" pthread_caml_link="-cclib -lpthread -cclib -lposix4";; *-*-dragon*) pthread_link="-pthread" pthread_caml_link="-cclib -pthread";; *-*-freebsd*) pthread_link="-pthread" pthread_caml_link="-cclib -pthread";; *-*-openbsd*) pthread_link="-pthread" pthread_caml_link="-cclib -pthread";; *-*-haiku*) pthread_link="" pthread_caml_link="";; *) pthread_link="-lpthread" pthread_caml_link="-cclib -lpthread";; esac if sh ./hasgot -i pthread.h $pthread_link pthread_self; then inf "POSIX threads library supported." systhread_support=true otherlibraries="$otherlibraries systhreads" bytecccompopts="$bytecccompopts -D_REENTRANT" nativecccompopts="$nativecccompopts -D_REENTRANT" case "$target" in *-*-freebsd*|*-*-dragonfly*) bytecccompopts="$bytecccompopts -D_THREAD_SAFE" nativecccompopts="$nativecccompopts -D_THREAD_SAFE";; *-*-openbsd*) bytecccompopts="$bytecccompopts -pthread" asppflags="$asppflags -pthread" nativecccompopts="$nativecccompopts -pthread";; esac inf "Options for linking with POSIX threads: $pthread_link" if sh ./hasgot $pthread_link sigwait; then inf "sigwait() found" echo "#define HAS_SIGWAIT" >> s.h fi else inf "POSIX threads not found." pthread_link="" fi else pthread_link="" fi echo "PTHREAD_LINK=$pthread_link" >> Makefile echo "PTHREAD_CAML_LINK=$pthread_caml_link" >> Makefile # Determine if the bytecode thread library is supported if test "$has_select" = "yes" \ && test "$has_setitimer" = "yes" \ && test "$has_gettimeofday" = "yes" \ && test "$has_wait" = "yes"; then inf "Bytecode threads library supported." otherlibraries="$otherlibraries threads" else inf "Bytecode threads library not supported (missing system calls)" fi # Determine the location of X include files and libraries # If the user specified -x11include and/or -x11lib, these settings # are used. Otherwise, we check whether there is pkg-config, and take # the flags from there. Otherwise, we search the location. x11_include="not found" x11_link="not found" if test -z "$x11_include_dir" -a -z "$x11_lib_dir"; then if pkg-config --exists x11 2>/dev/null; then x11_include=`pkg-config --cflags x11` x11_link=`pkg-config --libs x11` fi fi if test "$x11_include" = "not found"; then for dir in \ $x11_include_dir \ \ /usr/X11R7/include \ /usr/include/X11R7 \ /usr/local/X11R7/include \ /usr/local/include/X11R7 \ /opt/X11R7/include \ \ /usr/X11R6/include \ /usr/include/X11R6 \ /usr/local/X11R6/include \ /usr/local/include/X11R6 \ /opt/X11R6/include \ \ /usr/X11/include \ /usr/include/X11 \ /usr/local/X11/include \ /usr/local/include/X11 \ /opt/X11/include \ \ /usr/X11R5/include \ /usr/include/X11R5 \ /usr/local/X11R5/include \ /usr/local/include/X11R5 \ /usr/local/x11r5/include \ /opt/X11R5/include \ \ /usr/X11R4/include \ /usr/include/X11R4 \ /usr/local/X11R4/include \ /usr/local/include/X11R4 \ \ /usr/X386/include \ /usr/x386/include \ /usr/XFree86/include/X11 \ \ /usr/include \ /usr/local/include \ /usr/unsupported/include \ /usr/athena/include \ /usr/lpp/Xamples/include \ \ /usr/openwin/include \ /usr/openwin/share/include \ ; \ do if test -f $dir/X11/X.h; then x11_include_dir=$dir x11_include="-I$dir" break fi done if test "$x11_include" = "not found"; then x11_try_lib_dir='' else x11_try_lib_dir=`echo $x11_include_dir | sed -e 's|include|lib|'` fi for dir in \ $x11_lib_dir \ $x11_try_lib_dir \ \ /usr/X11R6/lib64 \ /usr/X11R6/lib \ /usr/lib/X11R6 \ /usr/local/X11R6/lib \ /usr/local/lib/X11R6 \ /opt/X11R6/lib \ \ /usr/X11/lib \ /usr/lib/X11 \ /usr/local/X11/lib \ /usr/local/lib/X11 \ /opt/X11/lib \ \ /usr/X11R5/lib \ /usr/lib/X11R5 \ /usr/local/X11R5/lib \ /usr/local/lib/X11R5 \ /usr/local/x11r5/lib \ /opt/X11R5/lib \ \ /usr/X11R4/lib \ /usr/lib/X11R4 \ /usr/local/X11R4/lib \ /usr/local/lib/X11R4 \ \ /usr/X386/lib \ /usr/x386/lib \ /usr/XFree86/lib/X11 \ \ /usr/lib64 \ /usr/lib \ /usr/local/lib \ /usr/unsupported/lib \ /usr/athena/lib \ /usr/lpp/Xamples/lib \ /lib/usr/lib/X11 \ \ /usr/openwin/lib \ /usr/openwin/share/lib \ \ /usr/lib/i386-linux-gnu \ /usr/lib/x86_64-linux-gnu \ ; \ do if test -f $dir/libX11.a || \ test -f $dir/libX11.so || \ test -f $dir/libX11.dll.a || \ test -f $dir/libX11.dylib || \ test -f $dir/libX11.sa; then if test $dir = /usr/lib; then x11_link="-lX11" else x11_libs="-L$dir" case "$target" in *-*-freebsd*|*-*-dragonfly*) x11_link="-L$dir -lX11";; *-kfreebsd*-gnu) x11_link="-L$dir -lX11";; *-*-*bsd*) x11_link="-R$dir -L$dir -lX11";; *) x11_link="-L$dir -lX11";; esac fi break fi done fi if test "x11_include" != "not found"; then if test "$x11_include" = "-I/usr/include"; then x11_include="" fi if sh ./hasgot $x11_include $x11_link -i X11/Xlib.h XrmInitialize; then inf "X11 works" else wrn "Cannot compile X11 program." x11_include="not found" fi fi has_graph=false if test "$x11_include" = "not found" || test "$x11_link" = "not found" then wrn 'X11 not found, the "graph" library will not be supported.' x11_include="not found" x11_link="not found" else inf "Options for compiling for X11: $x11_include" inf "Options for linking with X11: $x11_link" if test "$graph_wanted" = yes then has_graph=true otherlibraries="$otherlibraries graph" fi fi echo "X11_INCLUDES=$x11_include" >> Makefile echo "X11_LINK=$x11_link" >> Makefile # Look for BFD library if sh ./hasgot -DPACKAGE=ocaml -i bfd.h && \ sh ./hasgot -DPACKAGE=ocaml -lbfd -ldl -liberty -lz bfd_openr; then inf "BFD library found." echo "#define HAS_LIBBFD" >> s.h echo "LIBBFD_LINK=-lbfd -ldl -liberty -lz" >> Makefile echo LIBBFD_INCLUDE= >>Makefile elif sh ./hasgot -DPACKAGE=ocaml -I/opt/local/include -i bfd.h && \ sh ./hasgot -DPACKAGE=ocaml -L/opt/local/lib -lbfd -ldl \ -liberty -lz -lintl bfd_openr then # MacOSX with binutils from MacPorts inf "BFD library found." echo "#define HAS_LIBBFD" >> s.h echo "LIBBFD_LINK=-L/opt/local/lib -lbfd -ldl -liberty -lz -lintl" >> Makefile echo LIBBFD_INCLUDE=-I/opt/local/include >>Makefile else wrn "BFD library not found, 'objinfo' will be unable to display info" \ " on .cmxs files." echo "LIBBFD_LINK=" >> Makefile echo "LIBBFD_INCLUDE=" >> Makefile fi # Check whether assembler supports CFI directives asm_cfi_supported=false export as aspp if ! $with_cfi; then echo "CFI support: disabled by command-line option -no-cfi" elif sh ./tryassemble cfi.S; then echo "#define ASM_CFI_SUPPORTED" >> m.h asm_cfi_supported=true inf "Assembler supports CFI" else inf "Assembler does not support CFI" fi if test "$with_frame_pointers" = "true"; then case "$target,$cc" in x86_64-*-linux*,gcc*|x86_64-*-linux*,clang*) nativecccompopts="$nativecccompopts -g -fno-omit-frame-pointer" bytecccompopts="$bytecccompopts -g -fno-omit-frame-pointer" nativecclinkopts="$nativecclinkopts -g" echo "#define WITH_FRAME_POINTERS" >> m.h ;; *) err "Unsupported architecture with frame pointers";; esac fi if $no_naked_pointers; then echo "#define NO_NAKED_POINTERS" >> m.h fi # Check for mmap support for huge pages and contiguous heap if sh ./runtest mmap-huge.c; then has_huge_pages=true echo "#define HAS_HUGE_PAGES" >>s.h echo "#define HUGE_PAGE_SIZE (4 * 1024 * 1024)" >>s.h inf "mmap supports huge pages" else has_huge_pages=false fi # Spacetime profiling, including libunwind detection # The number of bits used for profiling information is configurable here. # The more bits used for profiling, the smaller will be Max_wosize. # Note that PROFINFO_WIDTH must still be defined even if not configuring # for Spacetime (see comment in byterun/caml/mlvalues.h on [Profinfo_hd]). echo "#define PROFINFO_WIDTH $profinfo_width" >> m.h if $with_profinfo; then echo "#define WITH_PROFINFO" >> m.h fi if $with_spacetime; then case "$arch,$system" in amd64,*) spacetime_supported=true ;; *) spacetime_supported=false ;; esac libunwind_warning=false if $spacetime_supported; then echo "Spacetime profiling will be available." echo "#define WITH_SPACETIME" >> m.h if $disable_libunwind; then has_libunwind=no libunwind_available=false echo "libunwind support for Spacetime profiling was explicitly disabled." else # On Mac OS X, we always use the system libunwind. if test "$libunwind_lib_dir" != ""; then case "$arch,$system" in amd64,macosx) inf "[WARNING] -libunwind* options are ignored on Mac OS X" libunwind_warning=true libunwind_lib="-framework System" libunwind_lib_temp="$libunwind_lib" # We need unwinding information at runtime, but since we use # -no_compact_unwind, we also need -keep_dwarf_unwind otherwise # the OS X linker will chuck away the DWARF-like (.eh_frame) # information. (Older versions of OS X don't provide this.) mkexe="$mkexe -Wl,-keep_dwarf_unwind" mksharedlib="$mksharedlib -Wl,-keep_dwarf_unwind" ;; *) libunwind_lib="-L$libunwind_lib_dir -lunwind -lunwind-x86_64" libunwind_lib_temp="-Xl $libunwind_lib" ;; esac else case "$arch,$system" in amd64,macosx) libunwind_lib="-framework System" libunwind_lib_temp="$libunwind_lib" mkexe="$mkexe -Wl,-keep_dwarf_unwind" mksharedlib="$mksharedlib -Wl,-keep_dwarf_unwind" ;; *) libunwind_lib="-lunwind -lunwind-x86_64" libunwind_lib_temp="$libunwind_lib" ;; esac fi if test "$libunwind_include_dir" != ""; then case "$arch,$system" in amd64,macosx) if ! $libunwind_warning; then inf "[WARNING] -libunwind* options are ignored on Mac OS X" fi libunwind_include="" ;; *) libunwind_include="-I$libunwind_include_dir" ;; esac else libunwind_include="" fi if sh ./hasgot -i libunwind.h $libunwind_lib_temp $libunwind_include; \ then echo "#define HAS_LIBUNWIND" >> s.h has_libunwind=yes libunwind_available=true echo "libunwind support for Spacetime profiling will be available." else has_libunwind=no libunwind_available=false echo "libunwind support for Spacetime profiling will not be available." fi fi else echo "Spacetime profiling is not available on 32-bit platforms." with_spacetime=false libunwind_available=false has_libunwind=no fi fi if ! $shared_libraries_supported; then with_cplugins=false fi if $with_fpic; then bytecccompopts="$bytecccompopts $sharedcccompopts" nativecccompopts="$nativecccompopts $sharedcccompopts" aspp="$aspp $sharedcccompopts" fi if $with_cplugins; then echo "#define CAML_WITH_CPLUGINS" >> m.h fi if $with_fpic; then echo "#define CAML_WITH_FPIC" >> m.h fi # Finish generated files cclibs="$cclibs $mathlib" echo "BYTECC=$bytecc $bytecccompopts" >> Makefile echo "BYTECODE_C_COMPILER=$bytecc $bytecccompopts $sharedcccompopts" \ >> Makefile echo "BYTECCCOMPOPTS=$byteccprivatecompopts" >> Makefile echo "BYTECCLINKOPTS=$bytecclinkopts" >> Makefile echo "BYTECCLIBS=$cclibs $dllib $curseslibs $pthread_link \ $instrumented_runtime_libs" >> Makefile echo "BYTECCRPATH=$byteccrpath" >> Makefile echo "EXE=$exe" >> Makefile echo "SUPPORTS_SHARED_LIBRARIES=$shared_libraries_supported" >> Makefile echo "SHAREDCCCOMPOPTS=$sharedcccompopts" >> Makefile echo "MKSHAREDLIBRPATH=$mksharedlibrpath" >> Makefile echo "NATDYNLINKOPTS=$natdynlinkopts" >> Makefile cat >> Makefile <> Makefile echo "MODEL=$model" >> Makefile echo "SYSTEM=$system" >> Makefile echo "NATIVECC=$nativecc $nativecccompopts" >> Makefile echo "NATIVE_C_COMPILER=$nativecc $nativecccompopts" >> Makefile echo "NATIVECCCOMPOPTS=$nativeccprivatecompopts" >> Makefile echo "NATIVECCPROFOPTS=$nativeccprofopts" >> Makefile echo "NATIVECCLINKOPTS=$nativecclinkopts" >> Makefile echo "NATIVECCRPATH=$nativeccrpath" >> Makefile echo "NATIVECCLIBS=$cclibs $dllib" >> Makefile echo "ASM=$as" >> Makefile echo "ASPP=$aspp" >> Makefile echo "ASPPPROFFLAGS=$asppprofflags" >> Makefile echo "PROFILING=$profiling" >> Makefile echo "DYNLINKOPTS=$dllib" >> Makefile echo "OTHERLIBRARIES=$otherlibraries" >> Makefile echo "CC_PROFILE=$cc_profile" >> Makefile echo "SYSTHREAD_SUPPORT=$systhread_support" >> Makefile echo "PACKLD=$partialld $nativecclinkopts -o\\ " >> Makefile echo "IFLEXDIR=$iflexdir" >> Makefile echo "O=o" >> Makefile echo "A=a" >> Makefile echo "SO=$SO" >> Makefile echo "EXT_OBJ=.o" >> Makefile echo "EXT_ASM=.s" >> Makefile echo "EXT_LIB=.a" >> Makefile echo "EXT_DLL=.$SO" >> Makefile echo "EXTRALIBS=" >> Makefile echo "CCOMPTYPE=cc" >> Makefile echo "TOOLCHAIN=$TOOLCHAIN" >> Makefile echo "NATDYNLINK=$natdynlink" >> Makefile echo "CMXS=$cmxs" >> Makefile echo "MKEXE=$mkexe" >> Makefile echo "MKEXEDEBUGFLAG=$mkexedebugflag" >> Makefile echo "MKDLL=$mksharedlib" >> Makefile echo "MKMAINDLL=$mkmaindll" >> Makefile echo "RUNTIMED=${debugruntime}" >>Makefile echo "RUNTIMEI=${with_instrumented_runtime}" >>Makefile echo "WITH_DEBUGGER=${with_debugger}" >>Makefile echo "WITH_OCAMLDOC=${with_ocamldoc}" >>Makefile echo "ASM_CFI_SUPPORTED=$asm_cfi_supported" >> Makefile echo "WITH_FRAME_POINTERS=$with_frame_pointers" >> Makefile echo "WITH_SPACETIME=$with_spacetime" >> Makefile echo "WITH_PROFINFO=$with_profinfo" >> Makefile echo "LIBUNWIND_AVAILABLE=$libunwind_available" >> Makefile echo "LIBUNWIND_INCLUDE_FLAGS=$libunwind_include" >> Makefile echo "LIBUNWIND_LINK_FLAGS=$libunwind_lib" >> Makefile echo "PROFINFO_WIDTH=$profinfo_width" >> Makefile echo "WITH_CPLUGINS=$with_cplugins" >> Makefile echo "WITH_FPIC=$with_fpic" >> Makefile echo "TARGET=$target" >> Makefile echo "HOST=$host" >> Makefile if [ "$ostype" = Cygwin ]; then echo "DIFF=diff -q --strip-trailing-cr" >>Makefile fi echo "FLAMBDA=$flambda" >> Makefile echo "SAFE_STRING=$safe_string" >> Makefile echo "AFL_INSTRUMENT=$afl_instrument" >> Makefile echo "MAX_TESTSUITE_DIR_RETRIES=$max_testsuite_dir_retries" >> Makefile rm -f tst hasgot.c rm -f ../m.h ../s.h ../Makefile mv m.h s.h Makefile .. # Print a summary inf inf "** Configuration summary **" inf inf "Directories where OCaml will be installed:" inf " binaries.................. $bindir" inf " standard library.......... $libdir" inf " manual pages.............. $mandir (with extension .$manext)" inf "Configuration for the bytecode compiler:" inf " C compiler used........... $bytecc" inf " options for compiling..... $bytecccompopts" inf " options for linking....... $bytecclinkopts $cclibs $dllib" \ "$curseslibs $pthread_link" if $shared_libraries_supported; then inf " shared libraries are supported" inf " options for compiling..... $sharedcccompopts $bytecccompopts" inf " command for building...... $mksharedlib -o lib.so" \ "$mksharedlibrpath/a/path objs" else inf " shared libraries not supported" fi inf "Configuration for the native-code compiler:" if test "$arch" = "none"; then inf " (not supported on this platform)" else if test "$model" = "default"; then inf " hardware architecture..... $arch" else inf " hardware architecture..... $arch ($model)" fi if test "$system" = "unknown"; then : ; else inf " OS variant................ $system" fi inf " C compiler used........... $nativecc" inf " options for compiling..... $nativecccompopts" inf " options for linking....... $nativecclinkopts $cclibs" inf " assembler ................ $as" inf " preprocessed assembler ... $aspp" if test "$asm_cfi_supported" = "true"; then inf " assembler supports CFI ... yes" else inf " assembler supports CFI ... no" fi if test "$with_frame_pointers" = "true"; then inf " with frame pointers....... yes" else inf " with frame pointers....... no" fi if $no_naked_pointers; then inf " naked pointers forbidden.. yes" else inf " naked pointers forbidden.. no" fi if $with_spacetime; then inf " spacetime profiling....... yes" inf " ... with libunwind...... $has_libunwind" else inf " spacetime profiling....... no" fi if $with_profinfo; then inf " reserved bits in header... $profinfo_width" else inf " reserved bits in header... no" fi case "$arch,$system" in amd64,macosx) ;; amd64,*) if test "$has_libunwind" = "yes"; then if test "$libunwind_include_dir" != ""; then inf " libunwind include dir..... $libunwind_include_dir" fi if test "$libunwind_lib_dir" != ""; then inf " libunwind library dir..... $libunwind_lib_dir" fi fi ;; *) ;; esac if $with_cplugins; then inf " C plugins................. yes" else inf " C plugins................. no" fi if $with_fpic; then inf " compile with -fPIC........ yes" else inf " compile with -fPIC........ no" fi inf " native dynlink ........... $natdynlink" if $profiling; then inf " profiling with gprof ..... supported" else inf " profiling with gprof ..... not supported" fi if test "$flambda" = "true"; then inf " using flambda middle-end . yes" else inf " using flambda middle-end . no" fi if test "$safe_string" = "true"; then inf " safe strings ............. yes" else inf " safe strings ............. no" fi if test "$afl_instrument" = "true"; then inf " afl-fuzz always enabled .. yes" else inf " afl-fuzz always enabled .. no" fi fi if test "$with_debugger" = "ocamldebugger"; then inf "Source-level replay debugger: supported" else inf "Source-level replay debugger: not supported" fi if $debugruntime; then inf "Debug runtime will be compiled and installed" fi if $with_instrumented_runtime; then inf "Instrumented runtime will be compiled and installed" fi inf "Additional libraries supported:" inf " $otherlibraries" inf "Configuration for the \"num\" library:" inf " target architecture ...... $bng_arch (asm level $bng_asm_level)" if $has_graph; then inf "Configuration for the \"graph\" library:" inf " options for compiling .... $x11_include" inf " options for linking ...... $x11_link" else inf "The \"graph\" library: not supported" fi inf inf "** OCaml configuration completed successfully **" inf if test ! -z "$MACOSX_DEPLOYMENT_TARGET"; then wrn "The environment variable MACOSX_DEPLOYMENT_TARGET is set.\n" \ "This will probably prevent compiling the OCaml system." fi