diff -r 7900110199cc -r 420dcc1dce80 erts/configure.in
--- a/erts/configure.in
+++ b/erts/configure.in
@@ -1090,6 +1090,49 @@ AC_CHECK_SIZEOF(long, 4)dnl Assumes all 
 AC_CHECK_SIZEOF(long, 4)dnl Assumes all cross compiling is to 32bit uP
 AC_CHECK_SIZEOF(void *, 4)dnl Assumes all cross compiling is to 32bit uP
 AC_CHECK_SIZEOF(long long, 0)
+
+dnl Type sizes needed by FFI
+AC_CHECK_SIZEOF(unsigned short, 0)
+AC_CHECK_SIZEOF(unsigned int, 0)
+AC_CHECK_SIZEOF(unsigned long, 0)
+AC_CHECK_SIZEOF(float, 0)
+AC_CHECK_SIZEOF(double, 0)
+AC_CHECK_SIZEOF(long double, 0)
+AC_CHECK_SIZEOF(size_t, 0)
+AC_CHECK_SIZEOF(ssize_t, 0)
+AC_CHECK_SIZEOF(off_t, 0)
+AC_CHECK_SIZEOF(pid_t, 0)
+
+dnl Compute and substitute type sizes (in bytes and bits)
+AC_SUBST([SIZEOF_UNSIGNED_SHORT], [$ac_cv_sizeof_unsigned_short])
+AC_SUBST([SIZEOF_SHORT],          [$ac_cv_sizeof_short])
+AC_SUBST([SIZEOF_UNSIGNED_INT],   [$ac_cv_sizeof_unsigned_int])
+AC_SUBST([SIZEOF_INT],            [$ac_cv_sizeof_int])
+AC_SUBST([SIZEOF_UNSIGNED_LONG],  [$ac_cv_sizeof_unsigned_long])
+AC_SUBST([SIZEOF_LONG],           [$ac_cv_sizeof_long])
+AC_SUBST([SIZEOF_FLOAT],          [$ac_cv_sizeof_float])
+AC_SUBST([SIZEOF_DOUBLE],         [$ac_cv_sizeof_double])
+AC_SUBST([SIZEOF_LONG_DOUBLE],    [$ac_cv_sizeof_long_double])
+AC_SUBST([SIZEOF_VOID_P],         [$ac_cv_sizeof_void_p])
+AC_SUBST([SIZEOF_SIZE_T],         [$ac_cv_sizeof_size_t])
+AC_SUBST([SIZEOF_SSIZE_T],        [$ac_cv_sizeof_ssize_t])
+AC_SUBST([SIZEOF_OFF_T],          [$ac_cv_sizeof_off_t])
+AC_SUBST([SIZEOF_PID_T],          [$ac_cv_sizeof_pid_t])
+
+AC_SUBST([UNSIGNED_SHORT_BITS], [$((SIZEOF_UNSIGNED_SHORT * 8))])
+AC_SUBST([SHORT_BITS],          [$((SIZEOF_SHORT * 8))])
+AC_SUBST([UNSIGNED_INT_BITS],   [$((SIZEOF_UNSIGNED_INT * 8))])
+AC_SUBST([INT_BITS],            [$((SIZEOF_INT * 8))])
+AC_SUBST([UNSIGNED_LONG_BITS],  [$((SIZEOF_UNSIGNED_LONG * 8))])
+AC_SUBST([LONG_BITS],           [$((SIZEOF_LONG * 8))])
+AC_SUBST([FLOAT_BITS],          [$((SIZEOF_FLOAT * 8))])
+AC_SUBST([DOUBLE_BITS],         [$((SIZEOF_DOUBLE * 8))])
+AC_SUBST([LONG_DOUBLE_BITS],    [$((SIZEOF_LONG_DOUBLE * 8))])
+AC_SUBST([VOID_P_BITS],         [$((SIZEOF_VOID_P * 8))])
+AC_SUBST([SIZE_T_BITS],         [$((SIZEOF_SIZE_T * 8))])
+AC_SUBST([SSIZE_T_BITS],        [$((SIZEOF_SSIZE_T * 8))])
+AC_SUBST([OFF_T_BITS],          [$((SIZEOF_OFF_T * 8))])
+AC_SUBST([PID_T_BITS],          [$((SIZEOF_PID_T * 8))])
 
 BITS64=
 
@@ -2958,5 +3001,6 @@ dnl
   ../lib/runtime_tools/c_src/$host/Makefile:../lib/runtime_tools/c_src/Makefile.in
   ../lib/tools/c_src/$host/Makefile:../lib/tools/c_src/Makefile.in
   ../lib/asn1/c_src/$host/Makefile:../lib/asn1/c_src/Makefile.in
+  ../lib/kernel/include/$host/ffi_hardcodes.hrl:../lib/kernel/include/ffi_hardcodes.hrl.in
   )
 
diff -r 7900110199cc -r 420dcc1dce80 lib/kernel/include/ffi_hardcodes.hrl.in
--- /dev/null
+++ b/lib/kernel/include/ffi_hardcodes.hrl.in
@@ -0,0 +1,169 @@
+%% @configure_input@
+
+%% ``The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved via the world wide web at http://www.erlang.org/.
+%% 
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%% 
+%% The Initial Developer of the Original Code is CRS4 - Center for
+%% Advanced Studies, Research and Development in Sardinia
+%% (http://www.crs4.it/). All Rights Reserved.''
+%% 
+%%     $Id$
+
+%% Foreign Function Interface (FFI) for Erlang/OTP
+%% Copyright (C) 2007 by CRS4 - http://www.crs4.it/
+%% Author: Alceste Scalas <alceste@crs4.it>
+
+-ifndef(__FFI_HARDCODES_HRL__).
+-define(__FFI_HARDCODES_HRL__, 1).
+
+%%
+%% Hardcoded type sizes for FFI types.  If you decide to use them, you
+%% may need to recompile your BEAM files in order to make them run on
+%% different platforms.
+%%
+-define(FFI_HARDCODED_SIZEOF_UCHAR, 1).
+-define(FFI_HARDCODED_UCHAR_BITS, 8).
+-define(FFI_HARDCODED_SIZEOF_SCHAR, 1).
+-define(FFI_HARDCODED_SCHAR_BITS, 8).
+
+-define(FFI_HARDCODED_SIZEOF_USHORT, @SIZEOF_UNSIGNED_SHORT@).
+-define(FFI_HARDCODED_USHORT_BITS, @UNSIGNED_SHORT_BITS@).
+-define(FFI_HARDCODED_SIZEOF_SSHORT, @SIZEOF_SHORT@).
+-define(FFI_HARDCODED_SSHORT_BITS, @SHORT_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_UINT, @SIZEOF_UNSIGNED_INT@).
+-define(FFI_HARDCODED_UINT_BITS, @UNSIGNED_INT_BITS@).
+-define(FFI_HARDCODED_SIZEOF_SINT, @SIZEOF_INT@).
+-define(FFI_HARDCODED_SINT_BITS, @INT_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_ULONG, @SIZEOF_UNSIGNED_LONG@).
+-define(FFI_HARDCODED_ULONG_BITS, @UNSIGNED_LONG_BITS@).
+-define(FFI_HARDCODED_SIZEOF_SLONG, @SIZEOF_LONG@).
+-define(FFI_HARDCODED_SLONG_BITS, @LONG_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_UINT8, 1).
+-define(FFI_HARDCODED_UINT8_BITS, 8).
+-define(FFI_HARDCODED_SIZEOF_SINT8, 1).
+-define(FFI_HARDCODED_SINT8_BITS, 8).
+
+-define(FFI_HARDCODED_SIZEOF_UINT16, 2).
+-define(FFI_HARDCODED_UINT16_BITS, 16).
+-define(FFI_HARDCODED_SIZEOF_SINT16, 2).
+-define(FFI_HARDCODED_SINT16_BITS, 16).
+
+-define(FFI_HARDCODED_SIZEOF_UINT32, 4).
+-define(FFI_HARDCODED_UINT32_BITS, 32).
+-define(FFI_HARDCODED_SIZEOF_SINT32, 4).
+-define(FFI_HARDCODED_SINT32_BITS, 32).
+
+-define(FFI_HARDCODED_SIZEOF_UINT64, 8).
+-define(FFI_HARDCODED_UINT64_BITS, 64).
+-define(FFI_HARDCODED_SIZEOF_SINT64, 8).
+-define(FFI_HARDCODED_SINT64_BITS, 64).
+
+-define(FFI_HARDCODED_SIZEOF_FLOAT, @SIZEOF_FLOAT@).
+-define(FFI_HARDCODED_FLOAT_BITS, @FLOAT_BITS@).
+-define(FFI_HARDCODED_SIZEOF_DOUBLE, @SIZEOF_DOUBLE@).
+-define(FFI_HARDCODED_DOUBLE_BITS, @DOUBLE_BITS@).
+-define(FFI_HARDCODED_SIZEOF_LONG_DOUBLE, @SIZEOF_LONG_DOUBLE@).
+-define(FFI_HARDCODED_LONG_DOUBLE_BITS, @LONG_DOUBLE_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_POINTER, @SIZEOF_VOID_P@).
+-define(FFI_HARDCODED_POINTER_BITS, @VOID_P_BITS@).
+-define(FFI_HARDCODED_SIZEOF_CSTRING, @SIZEOF_VOID_P@).
+-define(FFI_HARDCODED_CSTRING_BITS, @VOID_P_BITS@).
+-define(FFI_HARDCODED_SIZEOF_NONNULL, @SIZEOF_VOID_P@).
+-define(FFI_HARDCODED_NONNULL_BITS, @VOID_P_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_SIZE_T, @SIZEOF_SIZE_T@).
+-define(FFI_HARDCODED_SIZE_T_BITS, @SIZE_T_BITS@).
+-define(FFI_HARDCODED_SIZEOF_SSIZE_T, @SIZEOF_SSIZE_T@).
+-define(FFI_HARDCODED_SSIZE_T_BITS, @SSIZE_T_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_OFF_T, @SIZEOF_OFF_T@).
+-define(FFI_HARDCODED_OFF_T_BITS, @OFF_T_BITS@).
+
+-define(FFI_HARDCODED_SIZEOF_PID_T, @SIZEOF_PID_T@).
+-define(FFI_HARDCODED_PID_T_BITS, @PID_T_BITS@).
+
+%%
+%% Hardcoded bit syntax macros for FFI types.  If you decide to use
+%% them, you may need to recompile your BEAM files in order to make
+%% them run on different platforms.
+%%
+-define(FFI_HARDCODED_UCHAR,
+        ?FFI_HARDCODED_UCHAR_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SCHAR,
+        ?FFI_HARDCODED_SCHAR_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_USHORT,
+        ?FFI_HARDCODED_USHORT_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SSHORT,
+        ?FFI_HARDCODED_SSHORT_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_UINT,
+        ?FFI_HARDCODED_UINT_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SINT,
+        ?FFI_HARDCODED_SINT_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_ULONG,
+        ?FFI_HARDCODED_ULONG_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SLONG,
+        ?FFI_HARDCODED_SLONG_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_UINT8,
+        ?FFI_HARDCODED_UINT8_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SINT8,
+        ?FFI_HARDCODED_SINT8_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_UINT16,
+        ?FFI_HARDCODED_UINT16_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SINT16,
+        ?FFI_HARDCODED_SINT16_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_UINT32,
+        ?FFI_HARDCODED_UINT32_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SINT32,
+        ?FFI_HARDCODED_SINT32_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_UINT64,
+        ?FFI_HARDCODED_UINT64_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SINT64,
+        ?FFI_HARDCODED_SINT64_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_FLOAT,
+        ?FFI_HARDCODED_FLOAT_BITS/native-float).
+-define(FFI_HARDCODED_DOUBLE,
+        ?FFI_HARDCODED_DOUBLE_BITS/native-float).
+
+%% Sorry, no long double support
+%%-define(FFI_HARDCODED_LONG_DOUBLE,     
+%%        ?FFI_HARDCODED_LONG_DOUBLE_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_POINTER,
+        ?FFI_HARDCODED_POINTER_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_CSTRING,
+        ?FFI_HARDCODED_CSTRING_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_NONNULL,
+        ?FFI_HARDCODED_NONNULL_BITS/native-unsigned-integer).
+
+-define(FFI_HARDCODED_SIZE_T,
+        ?FFI_HARDCODED_SIZE_T_BITS/native-unsigned-integer).
+-define(FFI_HARDCODED_SSIZE_T,
+        ?FFI_HARDCODED_SSIZE_T_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_OFF_T,
+        ?FFI_HARDCODED_OFF_T_BITS/native-signed-integer).
+
+-define(FFI_HARDCODED_PID_T,
+        ?FFI_HARDCODED_PID_T_BITS/native-signed-integer).
+
+-endif. % __FFI_HARDCODES_HRL__
diff -r 7900110199cc -r 420dcc1dce80 lib/kernel/src/Makefile
--- a/lib/kernel/src/Makefile
+++ b/lib/kernel/src/Makefile
@@ -125,7 +125,8 @@ MODULES = \
 	wrap_log_reader \
 	zlib
 
-HRL_FILES= ../include/file.hrl ../include/inet.hrl
+HRL_FILES= ../include/file.hrl ../include/inet.hrl \
+	../include/$(TARGET)/ffi_hardcodes.hrl
 INTERNAL_HRL_FILES= application_master.hrl disk_log.hrl \
         net_address.hrl inet_dns.hrl inet_res.hrl \
         inet_boot.hrl inet_config.hrl inet_int.hrl \
@@ -152,7 +153,8 @@ APPUP_TARGET= $(EBIN)/$(APPUP_FILE)
 # FLAGS
 # ----------------------------------------------------
 
-ERL_COMPILE_FLAGS += +warn_obsolete_guard -I../include
+ERL_COMPILE_FLAGS += +warn_obsolete_guard -I../include -I../include/$(TARGET) \
+	-DERL_BUILD_TARGET="\"$(TARGET)\""
 
 # ----------------------------------------------------
 # Targets
@@ -226,6 +228,7 @@ list_preloaded:
 $(EBIN)/erl_epmd.beam: inet_int.hrl erl_epmd.hrl
 $(EBIN)/erl_prim_loader.beam: inet_boot.hrl
 $(EBIN)/file.beam: ../include/file.hrl
+$(EBIN)/ffi.beam: ../include/$(TARGET)/ffi_hardcodes.hrl
 $(EBIN)/gen_tcp.beam: inet_int.hrl
 $(EBIN)/gen_udp.beam: inet_int.hrl
 $(EBIN)/gen_sctp.beam: ../include/inet_sctp.hrl
diff -r 7900110199cc -r 420dcc1dce80 lib/kernel/src/ffi.erl
--- a/lib/kernel/src/ffi.erl
+++ b/lib/kernel/src/ffi.erl
@@ -40,12 +40,22 @@
 %%                                                               return type.
 -module(ffi).
 -author("Alceste Scalas <alceste@crs4.it>").
--export([call/3, buffer_to_binary/2, cstring_to_binary/1]).
+-export([call/3,
+	 buffer_to_binary/2, cstring_to_binary/1,
+	 sizeof/1, min/1, max/1,
+	 check/1]).
 
-%% @spec call(Port::port(), CFunc,
+-ifdef(ERL_BUILD_TARGET).
+%% We are being built, so the current include path allows this -include().
+-include("ffi_hardcodes.hrl").
+-else.
+-include_lib("kernel/include/ffi_hardcodes.hrl").
+-endif.
+
+%% @spec call(Port::port(), CFunc::cfunction(),
 %%            Args::[tagged_value()]) -> Ret::tagged_value()
-%%       CFunc = func_name() | func_index()
-%%               | tagged_func_name() | tagged_func_index()
+%%       cfunction() = func_name() | func_index()
+%%                     | tagged_func_name() | tagged_func_index()
 %%
 %% @doc Call the C function <code>CFunc</code> with the given list of
 %% arguments, using the port <code>Port</code>.  If the function was
@@ -168,6 +178,8 @@ try_preloaded_calls(Port, [Preload | Res
 %% Perform a FFI call using the given preload information.  Match the
 %% preloaded function signature with RetTypeTag and arguments type tags.
 do_preloaded_call(Port, RetTypeTag, Preload, Args) ->
+    check_arguments(Args),
+    
     %% Build and match function signature
     Sig = list_to_tuple([RetTypeTag] ++ [element(1, Arg) || Arg <- Args]),
     Sig = .proplists:get_value(signature, Preload),
@@ -183,6 +195,8 @@ do_preloaded_call(Port, RetTypeTag, Prel
 
 %% Perform a FFI call (without preload info).
 do_call(Port, RetTypeTag, CFunc, Args) ->
+    check_arguments(Args),
+    
     %% Build and match function signature
     Sig = list_to_tuple([RetTypeTag] ++ [element(1, Arg) || Arg <- Args]),
     RawArgs = [element(2, Arg) || Arg <- Args],
@@ -190,18 +204,35 @@ do_call(Port, RetTypeTag, CFunc, Args) -
     RetVal = .ffi:raw_call(Port, list_to_tuple([CFunc] ++ RawArgs), Sig),
     {RetTypeTag, RetVal}.
 
-%% @spec buffer_to_binary(TaggedNonnull, Size) -> binary()
-%%       TaggedNonnull = tuple(nonnull, integer())
+%% Raise an exception if any element in the arguments list is not a
+%% valid type-tagged value
+check_arguments(Args) ->
+    Check = .lists:all(fun check/1, Args),
+    if
+	Check ->
+	    ok;
+	true ->
+	    .erlang:error(badarg)
+    end.
+
+%% @spec buffer_to_binary(TaggedNonnull:nonnull(), Size) -> binary()
+%%       nonnull() = tuple(nonnull, integer())
 %%
 %% @doc Create a binary with a copy of <code>Size</code> bytes taken
 %% from the given C buffer (a type-tagged C non-null pointer).
 %%
 %% Return the new binary.
 buffer_to_binary({nonnull, Ptr}, Size) ->
-    .ffi:raw_buffer_to_binary(Ptr, Size).
+    IsValid = check({nonnull, Ptr}),
+    if
+	IsValid ->
+	    .ffi:raw_buffer_to_binary(Ptr, Size);
+	true ->
+	    .erlang:error(badarg)
+    end.
 
-%% @spec cstring_to_binary(TaggedCString) -> binary()
-%%       TaggedCString = tuple(cstring, integer())
+%% @spec cstring_to_binary(TaggedCString::cstring()) -> binary()
+%%       cstring() = tuple(cstring, integer())
 %%
 %% @doc Create a binary with a copy of the given C string (a
 %% type-tagged C non-null pointer).  The binary will include the trailing '\0'
@@ -209,4 +240,197 @@ buffer_to_binary({nonnull, Ptr}, Size) -
 %%
 %% Return the new binary.
 cstring_to_binary({cstring, Ptr}) ->
-    .ffi:raw_cstring_to_binary(Ptr).
+    IsValid = check({cstring, Ptr}),
+    if
+	IsValid ->
+	    .ffi:raw_cstring_to_binary(Ptr);
+	true ->
+	    .erlang:error(badarg)
+    end.
+
+%% @spec sizeof(TypeTag::type_tag()) -> integer()
+%%
+%% @doc Return the size of the given FFI type tag, on the current system.
+sizeof(uchar) ->
+    ?FFI_HARDCODED_SIZEOF_UCHAR;
+sizeof(schar) ->
+    ?FFI_HARDCODED_SIZEOF_SCHAR;
+sizeof(ushort) ->
+    ?FFI_HARDCODED_SIZEOF_USHORT;
+sizeof(sshort) ->
+    ?FFI_HARDCODED_SIZEOF_SSHORT;
+sizeof(uint) ->
+    ?FFI_HARDCODED_SIZEOF_UINT;
+sizeof(sint) ->
+    ?FFI_HARDCODED_SIZEOF_SINT;
+sizeof(ulong) ->
+    ?FFI_HARDCODED_SIZEOF_ULONG;
+sizeof(slong) ->
+    ?FFI_HARDCODED_SIZEOF_SLONG;
+sizeof(uint8) ->
+    ?FFI_HARDCODED_SIZEOF_UINT8;
+sizeof(sint8) ->
+    ?FFI_HARDCODED_SIZEOF_SINT8;
+sizeof(uint16) ->
+    ?FFI_HARDCODED_SIZEOF_UINT16;
+sizeof(sint16) ->
+    ?FFI_HARDCODED_SIZEOF_SINT16;
+sizeof(uint32) ->
+    ?FFI_HARDCODED_SIZEOF_UINT32;
+sizeof(sint32) ->
+    ?FFI_HARDCODED_SIZEOF_SINT32;
+sizeof(uint64) ->
+    ?FFI_HARDCODED_SIZEOF_UINT64;
+sizeof(sint64) ->
+    ?FFI_HARDCODED_SIZEOF_SINT64;
+sizeof(float) ->
+    ?FFI_HARDCODED_SIZEOF_FLOAT;
+sizeof(double) ->
+    ?FFI_HARDCODED_SIZEOF_DOUBLE;
+sizeof(longdouble) ->
+    ?FFI_HARDCODED_SIZEOF_LONG_DOUBLE;
+sizeof(pointer) ->
+    ?FFI_HARDCODED_SIZEOF_POINTER;
+sizeof(cstring) ->
+    ?FFI_HARDCODED_SIZEOF_POINTER;
+sizeof(nonnull) ->
+    ?FFI_HARDCODED_SIZEOF_POINTER;
+sizeof(size_t) ->
+    ?FFI_HARDCODED_SIZEOF_SIZE_T;
+sizeof(ssize_t) ->
+    ?FFI_HARDCODED_SIZEOF_SSIZE_T;
+sizeof(off_t) ->
+    ?FFI_HARDCODED_SIZEOF_OFF_T;
+sizeof(pid_t) ->
+    ?FFI_HARDCODED_SIZEOF_PID_T.
+
+%% @spec min(TypeTag::type_tag()) -> integer()
+%%
+%% @doc Return the minimum <em>integer</em> value allowed by the given
+%% FFI type.
+%%
+%% <strong>Note:</strong> only integer-based tagged values are
+%% supported (including C pointers).  Floating point values, in
+%% particular, are not supported.
+min(uchar) ->
+    0;
+min(schar) ->
+    -(1 bsl (?FFI_HARDCODED_SCHAR_BITS - 1));
+min(ushort) ->
+    0;
+min(sshort) ->
+    -(1 bsl (?FFI_HARDCODED_SSHORT_BITS - 1));
+min(uint) ->
+    0;
+min(sint) ->
+    -(1 bsl (?FFI_HARDCODED_SINT_BITS - 1));
+min(ulong) ->
+    0;
+min(slong) ->
+    -(1 bsl (?FFI_HARDCODED_SLONG_BITS - 1));
+min(uint8) ->
+    0;
+min(sint8) ->
+    -(1 bsl (?FFI_HARDCODED_SINT8_BITS - 1));
+min(uint16) ->
+    0;
+min(sint16) ->
+    -(1 bsl (?FFI_HARDCODED_SINT16_BITS - 1));
+min(uint32) ->
+    0;
+min(sint32) ->
+    -(1 bsl (?FFI_HARDCODED_SINT32_BITS - 1));
+min(uint64) ->
+    0;
+min(sint64) ->
+    -(1 bsl (?FFI_HARDCODED_SINT64_BITS - 1));
+min(pointer) ->
+    0;
+min(cstring) ->
+    1; % Cannot be NULL
+min(nonnull) ->
+    1; % Cannot be NULL
+min(size_t) ->
+    0;
+min(ssize_t) ->
+    -(1 bsl (?FFI_HARDCODED_SSIZE_T_BITS - 1));
+min(off_t) ->
+    -(1 bsl (?FFI_HARDCODED_OFF_T_BITS - 1));
+min(pid_t) ->
+    -(1 bsl (?FFI_HARDCODED_PID_T_BITS - 1)).
+
+%% @spec max(TypeTag::type_tag()) -> integer()
+%%
+%% @doc Return the maximum value allowed by the given
+%% <em>integer-based</em> FFI type.
+%%
+%% <strong>Note:</strong> only integer-based tagged values are
+%% supported (including C pointers).  Floating point values, in
+%% particular, are not supported.
+max(uchar) ->
+    (1 bsl ?FFI_HARDCODED_UCHAR_BITS) - 1;
+max(schar) ->
+    (1 bsl (?FFI_HARDCODED_SCHAR_BITS - 1)) - 1;
+max(ushort) ->
+    (1 bsl ?FFI_HARDCODED_USHORT_BITS) - 1;
+max(sshort) ->
+    (1 bsl (?FFI_HARDCODED_SSHORT_BITS - 1)) - 1;
+max(uint) ->
+    (1 bsl ?FFI_HARDCODED_UINT_BITS) - 1;
+max(sint) ->
+    (1 bsl (?FFI_HARDCODED_SINT_BITS - 1)) - 1;
+max(ulong) ->
+    (1 bsl ?FFI_HARDCODED_ULONG_BITS) - 1;
+max(slong) ->
+    (1 bsl (?FFI_HARDCODED_SLONG_BITS - 1)) - 1;
+max(uint8) ->
+    (1 bsl ?FFI_HARDCODED_UINT8_BITS) - 1;
+max(sint8) ->
+    (1 bsl (?FFI_HARDCODED_SINT8_BITS - 1)) - 1;
+max(uint16) ->
+    (1 bsl ?FFI_HARDCODED_UINT16_BITS) - 1;
+max(sint16) ->
+    (1 bsl (?FFI_HARDCODED_SINT16_BITS - 1)) - 1;
+max(uint32) ->
+    (1 bsl ?FFI_HARDCODED_UINT32_BITS) - 1;
+max(sint32) ->
+    (1 bsl (?FFI_HARDCODED_SINT32_BITS - 1)) - 1;
+max(uint64) ->
+    (1 bsl ?FFI_HARDCODED_UINT64_BITS) - 1;
+max(sint64) ->
+    (1 bsl (?FFI_HARDCODED_SINT64_BITS - 1)) - 1;
+max(pointer) ->
+    (1 bsl ?FFI_HARDCODED_POINTER_BITS) - 1;
+max(cstring) ->
+    (1 bsl ?FFI_HARDCODED_CSTRING_BITS) - 1;
+max(nonnull) ->
+    (1 bsl ?FFI_HARDCODED_NONNULL_BITS) - 1;
+max(size_t) ->
+    (1 bsl ?FFI_HARDCODED_SIZE_T_BITS) - 1;
+max(ssize_t) ->
+    (1 bsl (?FFI_HARDCODED_SSIZE_T_BITS - 1)) - 1;
+max(off_t) ->
+    (1 bsl (?FFI_HARDCODED_OFF_T_BITS - 1)) - 1;
+max(pid_t) ->
+    (1 bsl (?FFI_HARDCODED_PID_T_BITS - 1)) - 1.
+
+%% @spec check(TaggedValue::tagged_value()) -> true | false
+%%
+%% @doc Check that the given type-tagged value is valid.
+%%
+%% This function performs range and type checking.
+%%
+%% <strong>Note:</strong> only integer-based tagged values are
+%% completely supported (including C pointers).  Checks on floating
+%% point values will always return <code>true</code> (unless the
+%% tagged value is malformed).
+check({void, void}) ->
+    true;
+check({TypeTag, Value}) when ((TypeTag == float) or (TypeTag == double)
+			      or (TypeTag == longdouble))
+			     and is_float(Value) ->
+    true;
+check({TypeTag, Value}) when is_atom(TypeTag) and is_integer(Value) ->
+    (Value =< max(TypeTag)) and (Value >= min(TypeTag));
+check(_) ->
+    false.
