1AC_PREREQ([2.60])
2AC_INIT([Haskell base package], [1.0], [libraries@haskell.org], [base])
3
4# Safety check: Ensure that we are in the correct source directory.
5AC_CONFIG_SRCDIR([include/HsBase.h])
6
7AC_CONFIG_HEADERS([include/HsBaseConfig.h include/EventConfig.h])
8
9AC_PROG_CC
10dnl make extensions visible to allow feature-tests to detect them lateron
11AC_USE_SYSTEM_EXTENSIONS
12
13AC_MSG_CHECKING(for WINDOWS platform)
14case $host_alias in
15    *mingw32*|*mingw64*|*cygwin*|*msys*)
16        WINDOWS=YES;;
17    *)
18        WINDOWS=NO;;
19esac
20AC_MSG_RESULT($WINDOWS)
21
22# do we have long longs?
23AC_CHECK_TYPES([long long])
24
25# check for specific header (.h) files that we are interested in
26AC_CHECK_HEADERS([ctype.h errno.h fcntl.h inttypes.h limits.h signal.h sys/file.h sys/resource.h sys/select.h sys/stat.h sys/syscall.h sys/time.h sys/timeb.h sys/timers.h sys/times.h sys/types.h sys/utsname.h sys/wait.h termios.h time.h unistd.h utime.h windows.h winsock.h langinfo.h poll.h sys/epoll.h sys/event.h sys/eventfd.h sys/socket.h])
27
28# Enable large file support. Do this before testing the types ino_t, off_t, and
29# rlim_t, because it will affect the result of that test.
30AC_SYS_LARGEFILE
31
32dnl ** check for wide-char classifications
33dnl FreeBSD has an emtpy wctype.h, so test one of the affected
34dnl functions if it's really there.
35AC_CHECK_HEADERS([wctype.h], [AC_CHECK_FUNCS(iswspace)])
36
37AC_CHECK_FUNCS([lstat])
38AC_CHECK_LIB([rt], [clock_gettime])
39AC_CHECK_FUNCS([clock_gettime])
40AC_CHECK_FUNCS([getclock getrusage times])
41AC_CHECK_FUNCS([_chsize ftruncate])
42
43AC_CHECK_FUNCS([epoll_ctl eventfd kevent kevent64 kqueue poll])
44
45# event-related fun
46
47if test "$ac_cv_header_sys_epoll_h" = yes && test "$ac_cv_func_epoll_ctl" = yes; then
48  AC_DEFINE([HAVE_EPOLL], [1], [Define if you have epoll support.])
49fi
50
51if test "$ac_cv_header_sys_event_h" = yes && test "$ac_cv_func_kqueue" = yes; then
52  AC_DEFINE([HAVE_KQUEUE], [1], [Define if you have kqueue support.])
53
54  AC_CHECK_SIZEOF([kev.filter], [], [#include <sys/event.h>
55struct kevent kev;])
56
57  AC_CHECK_SIZEOF([kev.flags], [], [#include <sys/event.h>
58struct kevent kev;])
59fi
60
61if test "$ac_cv_header_poll_h" = yes && test "$ac_cv_func_poll" = yes; then
62  AC_DEFINE([HAVE_POLL], [1], [Define if you have poll support.])
63fi
64
65# Linux open file descriptor locks
66AC_CHECK_DECL([F_OFD_SETLK], [
67  AC_DEFINE([HAVE_OFD_LOCKING], [1], [Define if you have open file descriptor lock support.])
68], [], [
69  #include <unistd.h>
70  #include <fcntl.h>
71])
72
73# flock
74AC_CHECK_FUNCS([flock])
75if test "$ac_cv_header_sys_file_h" = yes && test "$ac_cv_func_flock" = yes; then
76  AC_DEFINE([HAVE_FLOCK], [1], [Define if you have flock support.])
77fi
78
79# unsetenv
80AC_CHECK_FUNCS([unsetenv])
81
82###  POSIX.1003.1 unsetenv returns 0 or -1 (EINVAL), but older implementations
83###  in common use return void.
84AC_CACHE_CHECK([return type of unsetenv], fptools_cv_func_unsetenv_return_type,
85  [AC_EGREP_HEADER(changequote(<, >)<void[      ]+unsetenv>changequote([, ]),
86                   stdlib.h,
87                   [fptools_cv_func_unsetenv_return_type=void],
88                   [fptools_cv_func_unsetenv_return_type=int])])
89case "$fptools_cv_func_unsetenv_return_type" in
90  "void" )
91    AC_DEFINE([UNSETENV_RETURNS_VOID], [1], [Define if stdlib.h declares unsetenv to return void.])
92  ;;
93esac
94
95dnl--------------------------------------------------------------------
96dnl * Deal with arguments telling us iconv is somewhere odd
97dnl--------------------------------------------------------------------
98
99AC_ARG_WITH([iconv-includes],
100  [AS_HELP_STRING([--with-iconv-includes],
101    [directory containing iconv.h])],
102    [ICONV_INCLUDE_DIRS=$withval],
103    [ICONV_INCLUDE_DIRS=])
104
105AC_ARG_WITH([iconv-libraries],
106  [AS_HELP_STRING([--with-iconv-libraries],
107    [directory containing iconv library])],
108    [ICONV_LIB_DIRS=$withval; LDFLAGS="-L$withval $LDFLAGS"],
109    [ICONV_LIB_DIRS=])
110
111AC_SUBST(ICONV_INCLUDE_DIRS)
112AC_SUBST(ICONV_LIB_DIRS)
113
114# map standard C types and ISO types to Haskell types
115FPTOOLS_CHECK_HTYPE(char)
116FPTOOLS_CHECK_HTYPE(signed char)
117FPTOOLS_CHECK_HTYPE(unsigned char)
118FPTOOLS_CHECK_HTYPE(short)
119FPTOOLS_CHECK_HTYPE(unsigned short)
120FPTOOLS_CHECK_HTYPE(int)
121FPTOOLS_CHECK_HTYPE(unsigned int)
122FPTOOLS_CHECK_HTYPE(long)
123FPTOOLS_CHECK_HTYPE(unsigned long)
124if test "$ac_cv_type_long_long" = yes; then
125FPTOOLS_CHECK_HTYPE(long long)
126FPTOOLS_CHECK_HTYPE(unsigned long long)
127fi
128FPTOOLS_CHECK_HTYPE(bool)
129FPTOOLS_CHECK_HTYPE(float)
130FPTOOLS_CHECK_HTYPE(double)
131FPTOOLS_CHECK_HTYPE(ptrdiff_t)
132FPTOOLS_CHECK_HTYPE(size_t)
133FPTOOLS_CHECK_HTYPE(wchar_t)
134FPTOOLS_CHECK_HTYPE(sig_atomic_t)
135FPTOOLS_CHECK_HTYPE(clock_t)
136FPTOOLS_CHECK_HTYPE(time_t)
137FPTOOLS_CHECK_HTYPE(useconds_t)
138FPTOOLS_CHECK_HTYPE_ELSE(suseconds_t,
139                         [if test "$WINDOWS" = "YES"
140                          then
141                              AC_CV_NAME=Int32
142                              AC_CV_NAME_supported=yes
143                          else
144                              AC_MSG_ERROR([type not found])
145                          fi])
146FPTOOLS_CHECK_HTYPE(dev_t)
147FPTOOLS_CHECK_HTYPE(ino_t)
148FPTOOLS_CHECK_HTYPE(mode_t)
149FPTOOLS_CHECK_HTYPE(off_t)
150FPTOOLS_CHECK_HTYPE(pid_t)
151FPTOOLS_CHECK_HTYPE(gid_t)
152FPTOOLS_CHECK_HTYPE(uid_t)
153FPTOOLS_CHECK_HTYPE(cc_t)
154FPTOOLS_CHECK_HTYPE(speed_t)
155FPTOOLS_CHECK_HTYPE(tcflag_t)
156FPTOOLS_CHECK_HTYPE(nlink_t)
157FPTOOLS_CHECK_HTYPE(ssize_t)
158FPTOOLS_CHECK_HTYPE(rlim_t)
159FPTOOLS_CHECK_HTYPE(blksize_t)
160FPTOOLS_CHECK_HTYPE(blkcnt_t)
161FPTOOLS_CHECK_HTYPE(clockid_t)
162FPTOOLS_CHECK_HTYPE(fsblkcnt_t)
163FPTOOLS_CHECK_HTYPE(fsfilcnt_t)
164FPTOOLS_CHECK_HTYPE(id_t)
165FPTOOLS_CHECK_HTYPE(key_t)
166FPTOOLS_CHECK_HTYPE(timer_t)
167FPTOOLS_CHECK_HTYPE(socklen_t)
168FPTOOLS_CHECK_HTYPE(nfds_t)
169
170FPTOOLS_CHECK_HTYPE(intptr_t)
171FPTOOLS_CHECK_HTYPE(uintptr_t)
172FPTOOLS_CHECK_HTYPE(intmax_t)
173FPTOOLS_CHECK_HTYPE(uintmax_t)
174
175# test errno values
176FP_CHECK_CONSTS([E2BIG EACCES EADDRINUSE EADDRNOTAVAIL EADV EAFNOSUPPORT EAGAIN EALREADY EBADF EBADMSG EBADRPC EBUSY ECHILD ECOMM ECONNABORTED ECONNREFUSED ECONNRESET EDEADLK EDESTADDRREQ EDIRTY EDOM EDQUOT EEXIST EFAULT EFBIG EFTYPE EHOSTDOWN EHOSTUNREACH EIDRM EILSEQ EINPROGRESS EINTR EINVAL EIO EISCONN EISDIR ELOOP EMFILE EMLINK EMSGSIZE EMULTIHOP ENAMETOOLONG ENETDOWN ENETRESET ENETUNREACH ENFILE ENOBUFS ENODATA ENODEV ENOENT ENOEXEC ENOLCK ENOLINK ENOMEM ENOMSG ENONET ENOPROTOOPT ENOSPC ENOSR ENOSTR ENOSYS ENOTBLK ENOTCONN ENOTDIR ENOTEMPTY ENOTSOCK ENOTTY ENXIO EOPNOTSUPP EPERM EPFNOSUPPORT EPIPE EPROCLIM EPROCUNAVAIL EPROGMISMATCH EPROGUNAVAIL EPROTO EPROTONOSUPPORT EPROTOTYPE ERANGE EREMCHG EREMOTE EROFS ERPCMISMATCH ERREMOTE ESHUTDOWN ESOCKTNOSUPPORT ESPIPE ESRCH ESRMNT ESTALE ETIME ETIMEDOUT ETOOMANYREFS ETXTBSY EUSERS EWOULDBLOCK EXDEV ENOCIGAR ENOTSUP], [#include <stdio.h>
177#include <errno.h>])
178
179# we need SIGINT in TopHandler.lhs
180FP_CHECK_CONSTS([SIGINT], [
181#if HAVE_SIGNAL_H
182#include <signal.h>
183#endif])
184
185dnl ** can we open files in binary mode?
186FP_CHECK_CONST([O_BINARY], [#include <fcntl.h>], [0])
187
188# We don't use iconv or libcharset on Windows, but if configure finds
189# them then it can cause problems. So we don't even try looking if
190# we are on Windows.
191# See http://www.haskell.org/pipermail/cvs-ghc/2011-September/065980.html
192if test "$WINDOWS" = "NO"
193then
194
195# We can't just use AC_SEARCH_LIBS for this, as on OpenBSD the iconv.h
196# header needs to be included as iconv_open is #define'd to something
197# else. We therefore use our own FP_SEARCH_LIBS_PROTO, which allows us
198# to give prototype text.
199FP_SEARCH_LIBS_PROTO(iconv,
200                     [
201#include <stddef.h>
202#include <iconv.h>
203                      ],
204                     [iconv_t cd;
205                      cd = iconv_open("", "");
206                      iconv(cd,NULL,NULL,NULL,NULL);
207                      iconv_close(cd);],
208                     iconv,
209                     [EXTRA_LIBS="$EXTRA_LIBS $ac_lib"],
210                     [AC_MSG_ERROR([iconv is required on non-Windows platforms])])
211
212# If possible, we use libcharset instead of nl_langinfo(CODESET) to
213# determine the current locale's character encoding.  Allow the user
214# to disable this with --without-libcharset if they don't want a
215# dependency on libcharset.
216AC_ARG_WITH([libcharset],
217  [AS_HELP_STRING([--with-libcharset],
218    [Use libcharset [default=only if available]])],
219  [],
220  [with_libcharset=check])
221
222AS_IF([test "x$with_libcharset" != xno],
223  FP_SEARCH_LIBS_PROTO(
224    [locale_charset],
225    [#include <libcharset.h>],
226    [const char* charset = locale_charset();],
227    [charset],
228    [AC_DEFINE([HAVE_LIBCHARSET], [1], [Define to 1 if you have libcharset.])
229     EXTRA_LIBS="$EXTRA_LIBS $ac_lib"]
230  ))
231
232fi
233
234dnl Calling AC_CHECK_TYPE(T) makes AC_CHECK_SIZEOF(T) abort on failure
235dnl instead of considering sizeof(T) as 0.
236AC_CHECK_TYPE([struct MD5Context], [], [AC_MSG_ERROR([internal error])], [#include "include/md5.h"])
237AC_CHECK_SIZEOF([struct MD5Context], [], [#include "include/md5.h"])
238
239AC_SUBST(EXTRA_LIBS)
240AC_CONFIG_FILES([base.buildinfo])
241
242AC_OUTPUT
243