diff -r 34b57ba8b406 -r 54b43754447d erts/emulator/beam/erl_bif_ffi.c
--- a/erts/emulator/beam/erl_bif_ffi.c
+++ b/erts/emulator/beam/erl_bif_ffi.c
@@ -70,6 +70,8 @@ BIF_RETTYPE ffi_raw_buffer_to_binary_2(B
 }
 
 #else /* HAVE_LIBFFI */
+
+#include "erl_bif_ffi_endianness.h"
 
 /*
  * Some "special" types, that need particular care by the FFI.
@@ -218,7 +220,7 @@ BIF_RETTYPE ffi_raw_call_3(BIF_ALIST_3)
 
     {
 	Uint nargs_1 = nargs - 1;
-        Sint64 retval[2]; /* FFI call return value (must be large & aligned) */
+        Sint64 retval[2]; /* FFI return value (must be large & aligned) */
         ffi_cif cif;
         ffi_type* ftypes[nargs]; /* Return type + call arguments types */
         void* avalues[nargs_1]; /* Pointers to arguments data */
@@ -344,7 +346,7 @@ BIF_RETTYPE ffi_raw_call_2(BIF_ALIST_2)
 
     {
 	Uint nargs_1 = nargs - 1;
-        Sint64 retval[2]; /* FFI call return value (must be large & aligned) */
+        Sint64 retval[2]; /* FFI return value (must be large & aligned) */
         void* avalues[nargs_1]; /* Pointers to arguments data */
         void* tmp_allocs[2*nargs_1]; /* Buffers allocated with ERTS_ALC_T_TMP */
         ErlDrvBinary* drv_allocs[nargs_1]; /* Driver bins that need free()d */
@@ -407,11 +409,11 @@ BIF_RETTYPE ffi_raw_cstring_to_binary_1(
     char* ptr;
     Eterm res;
 
-    if (is_big(BIF_ARG_1))
-	ptr = *((char**)big_v(BIF_ARG_1));
-    else if (is_small(BIF_ARG_1))
+    if (is_big(BIF_ARG_1)) {
+	FFI_BIG_TO_UNSIGNED_NATIVE(&ptr, BIF_ARG_1, char*);
+    } else if (is_small(BIF_ARG_1)) {
 	ptr = (char*)unsigned_val(BIF_ARG_1);
-    else {
+    } else {
     error:
 	BIF_ERROR(BIF_P, BADARG);
     }
@@ -428,15 +430,15 @@ BIF_RETTYPE ffi_raw_cstring_to_binary_1(
  * buffer (a pointer possibly obtained with a FFI call) */
 BIF_RETTYPE ffi_raw_buffer_to_binary_2(BIF_ALIST_2)
 {
-    char* ptr;
+    byte* ptr;
     int size;
     Eterm res;
 
-    if (is_big(BIF_ARG_1))
-	ptr = *((char**)big_v(BIF_ARG_1));
-    else if (is_small(BIF_ARG_1))
-	ptr = (char*)unsigned_val(BIF_ARG_1);
-    else {
+    if (is_big(BIF_ARG_1)) {
+	FFI_BIG_TO_UNSIGNED_NATIVE(&ptr, BIF_ARG_1, byte*);
+    } else if (is_small(BIF_ARG_1)) {
+	ptr = (byte*)unsigned_val(BIF_ARG_1);
+    } else {
     error:
 	BIF_ERROR(BIF_P, BADARG);
     }
@@ -448,7 +450,7 @@ BIF_RETTYPE ffi_raw_buffer_to_binary_2(B
 	BIF_ERROR(BIF_P, BADARG);
     size = (int)unsigned_val(BIF_ARG_2);
 
-    res = new_binary(BIF_P, (byte*)ptr, size);
+    res = new_binary(BIF_P, ptr, size);
 
     BIF_RET(res);
 }
@@ -504,11 +506,7 @@ static int build_ffi_args_array(Eterm ar
     ffi_type* ftype;
     Eterm arg, bitoffs, bitsize;
     Eterm *binval;
-    byte* ptr;
-    int tmpint;
-    long tmplong;
-    Sint32 tmps32;
-    Sint64 tmps64;
+    const byte* ptr;
     Binary *bin;
     ErlDrvBinary *drvbin;
 
@@ -543,8 +541,7 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_uint) {
             /* Integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
-                *((unsigned int*) buf) = *((unsigned int*) ptr);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, unsigned int);
             } else if (is_small(arg))
                 *((unsigned int*) buf) = unsigned_val(arg);
             else
@@ -555,14 +552,12 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_sint) {
             /* Integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, unsigned int);
                 if (big_sign(arg)) {
                     /* Erlang big integers keep a sign byte, instead of using
                      * 2's complement */
-                    tmpint = -(*((int*)ptr));
-                    *((int*) buf) = tmpint;
-                } else
-                    *((int*) buf) = *((int*) ptr);
+		    *(int*)buf = -(*(unsigned int*)buf);
+                }
             } else if (is_small(arg))
                 *((int*) buf) = signed_val(arg);
             else
@@ -574,22 +569,22 @@ static int build_ffi_args_array(Eterm ar
 		   || ftype == &erl_ffi_type_cstring
 		   || ftype == &erl_ffi_type_nonnull) {
             /* Pointers may be taken either from binaries, smalls or bigs */
-            if (is_binary(arg))
+            if (is_binary(arg)) {
                 ERTS_GET_BINARY_BYTES(arg, ptr, bitoffs, bitsize);
-            else if (is_big(arg))
-                ptr = *((void**)big_v(arg));
-            else if (is_small(arg))
-                ptr = (void*)unsigned_val(arg);
-            else
+		*(const byte**)buf = ptr;
+            } else if (is_big(arg)) {
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, byte*);
+            } else if (is_small(arg)) {
+		*((byte**)buf) = (byte*)unsigned_val(arg);
+            } else
                 return ERL_FFI_STATUS_BADARG;
-	    if ((ftype != &ffi_type_pointer) && (ptr == NULL)) {
+	    if ((ftype != &ffi_type_pointer) && (*(byte**)buf == NULL)) {
 		/* 'cstring' and 'nonnull' may not be NULL */
 		return ERL_FFI_STATUS_BADARG;
 	    }
-            *((void**)buf) = ptr;
             call_ptrs[i] = buf;
-            offset += sizeof(void*);
-            buf += sizeof(void*);
+            offset += sizeof(byte*);
+            buf += sizeof(byte*);
         } else if (ftype == &ffi_type_ushort) {
             if (is_not_small(arg))
                 return ERL_FFI_STATUS_BADARG;
@@ -607,8 +602,7 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_ulong) {
             /* Long integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
-                *((unsigned long*) buf) = *((unsigned long*) ptr);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, unsigned long);
             } else if (is_small(arg))
                 *((unsigned long*) buf) = unsigned_val(arg);
             else
@@ -619,14 +613,12 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_slong) {
             /* Integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, unsigned long);
                 if (big_sign(arg)) {
                     /* Erlang big integers keep a sign byte, instead of using
                      * 2's complement */
-                    tmplong = -(*((long*)ptr));
-                    *((long*) buf) = tmplong;
-                } else
-                    *((long*) buf) = *((long*) ptr);
+		    *(long*)buf = -(*(unsigned long*)buf);
+                }
             } else if (is_small(arg))
                 *((long*) buf) = signed_val(arg);
             else
@@ -667,8 +659,7 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_uint32) {
             /* 32-bit integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
-                *((Uint32*) buf) = *((Uint32*) ptr);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, Uint32);
             } else if (is_small(arg))
                 *((Uint32*) buf) = (Uint32)unsigned_val(arg);
             else
@@ -679,14 +670,12 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_sint32) {
             /* 32-bit integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, Uint32);
                 if (big_sign(arg)) {
                     /* Erlang big integers keep a sign byte, instead of using
                      * 2's complement */
-                    tmps32 = -(*((Sint32*)ptr));
-                    *((Sint32*) buf) = tmps32;
-                } else
-                    *((Sint32*) buf) = *((Sint32*) ptr);
+		    *(Sint32*)buf = -(*(Uint32*)buf);
+                }
             } else if (is_small(arg))
                 *((Sint32*) buf) = signed_val(arg);
             else
@@ -697,23 +686,10 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_uint64) {
             /* 64-bit integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-		ptr = (void*)big_v(arg);
-#ifndef ARCH_64
-		/* On 32-bit architectures, a 64-bit value may fit in
-		 * in a variable number of words. */
-		if (4 == big_size(arg) * sizeof(digit_t)) {
-		    /* It is a 32-bit value */
-		    *((Uint64*) buf) = (Uint64)(*((Uint32*) ptr));
-		} else {
-		    /* It is a 64-bit value */
-		    *((Uint64*) buf) = *((Uint64*) ptr);
-		}
-#else /* ARCH_64 */
-                *((Uint64*) buf) = *((Uint64*) ptr);
-#endif
-            } else if (is_small(arg))
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, Uint64);
+            } else if (is_small(arg)) {
                 *((Uint64*) buf) = unsigned_val(arg);
-            else
+            } else
                 return ERL_FFI_STATUS_BADARG;
             call_ptrs[i] = buf;
             offset += sizeof(Uint64);
@@ -721,41 +697,12 @@ static int build_ffi_args_array(Eterm ar
         } else if (ftype == &ffi_type_sint64) {
             /* Integers may be taken either from smalls or bigs */
             if (is_big(arg)) {
-                ptr = (void*)big_v(arg);
-#ifndef ARCH_64
-		/* On 32-bit architectures, a 64-bit value may fit in
-		 * in a variable number of words. */
-		if (4 == big_size(arg) * sizeof(digit_t)) {
-		    /* It is a 32-bit value */
-		    if (big_sign(arg)) {
-			/* Erlang big integers keep a sign byte,
-			 * instead of using 2's complement */
-			tmps64 = -(*((Sint32*)ptr));
-			*((Sint64*) buf) = tmps64;
-		    } else {
-			*((Sint64*) buf) = *((Sint32*) ptr);
-		    }
-		} else {
-		    /* It is a 64-bit value */
-		    if (big_sign(arg)) {
-			/* Erlang big integers keep a sign byte,
-			 * instead of using 2's complement */
-			tmps64 = -(*((Sint64*)ptr));
-			*((Sint64*) buf) = tmps64;
-		    } else {
-			*((Sint64*) buf) = *((Sint64*) ptr);
-		    }
-		}
-#else /* ARCH_64 */
+		FFI_BIG_TO_UNSIGNED_NATIVE(buf, arg, Uint64);
                 if (big_sign(arg)) {
                     /* Erlang big integers keep a sign byte, instead of using
                      * 2's complement */
-                    tmps64 = -(*((Sint64*)ptr));
-                    *((Sint64*) buf) = tmps64;
-                } else {
-                    *((Sint64*) buf) = *((Sint64*) ptr);
-		}
-#endif
+		    *((Sint64*) buf) = -(*(Uint64*)buf);
+                }
             } else if (is_small(arg))
                 *((Sint64*) buf) = signed_val(arg);
             else
@@ -846,13 +793,6 @@ static Eterm build_ffi_return_term(Proce
     FloatDef f;
     Eterm res;
     Eterm* hp;
-    long tmplong;
-    unsigned long tmpulong;
-    Sint64 tmps64;
-    Uint64 tmpu64;
-#ifndef ARCH_64
-    Uint32 tmpu32;
-#endif
     ProcBin *pb;
     Binary *bin;
     byte *ptr;
@@ -870,120 +810,73 @@ static Eterm build_ffi_return_term(Proce
         res = make_float(hp);
         PUT_DOUBLE(f, hp);
     } else if (rtype == &ffi_type_uint) {
-        res = erts_make_integer(*((unsigned int*) retval), p);
+        res = erts_make_integer(FFI_BUF_VALUE(retval, unsigned int,
+					      unsigned int), p);
     } else if (rtype == &ffi_type_sint) {
-        res = erts_make_signed_integer(*((int*) retval), p);
+        res = erts_make_signed_integer(FFI_BUF_VALUE(retval, int, int), p);
     } else if (rtype == &ffi_type_pointer
 	       || rtype == &erl_ffi_type_cstring
 	       || rtype == &erl_ffi_type_nonnull) {
-	if ((rtype != &ffi_type_pointer) && (*((byte**)retval) == NULL)) {
+	if ((rtype != &ffi_type_pointer)
+	    && (FFI_BUF_VALUE(retval, void*, void*)) == NULL) {
 	    /* 'cstring' and 'nonnull' may not be NULL */
 	    /* FIXME: a more descriptive error is definitely needed */
 	    BIF_ERROR(p, BADARG);
 	}
-	/* A pointer alwais fits in a Uint */
-        res = erts_make_integer(*((Uint*) retval), p);
+	/* A pointer has the size of a word, and alwais fits in a Uint */
+	res = erts_make_integer(FFI_BUF_VALUE(retval, Uint, Uint), p);
     } else if (rtype == &ffi_type_ushort) {
-        res = make_small(*((unsigned short*) retval));
+        res = FFI_NATIVE_TO_SMALL(retval, unsigned short, unsigned short);
     } else if (rtype == &ffi_type_sshort) {
-        res = make_small(*((short*) retval));
+	res = FFI_NATIVE_TO_SMALL(retval, short, short);
     } else if (rtype == &ffi_type_ulong) {
-	if (IS_USMALL(0, *((unsigned long*)retval))) {
-	    res = make_small(*((unsigned long*)retval));
+	if (FFI_BUF_IS_USMALL(retval, unsigned long)) {
+	    res = FFI_NATIVE_TO_SMALL(retval, unsigned long, Uint);
 	} else {
-	    hp = ArithAlloc(p, 1 + WSIZE(sizeof(unsigned long)));
-	    res = bytes_to_big((byte*)retval, sizeof(unsigned long), 0, hp);
+	    res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, unsigned long, 0);
 	}
     } else if (rtype == &ffi_type_slong) {
-	if (IS_SSMALL(*((long*)retval))) {
-	    res = make_small(*((long*)retval));
+	if (FFI_BUF_IS_SSMALL(retval, long)) {
+	    res = FFI_NATIVE_TO_SMALL(retval, long, Sint);
 	} else {
-	    hp = ArithAlloc(p, 1 + WSIZE(sizeof(long)));
-	    tmplong = *((long*)retval);
-	    if (tmplong >= 0)
-		res = bytes_to_big((byte*)&tmplong, sizeof(long), 0, hp);
-	    else {
-		/* Erlang big integers keep a sign byte, instead of using
-		 * 2's complement */
-		tmpulong = -tmplong;
-		res = bytes_to_big((byte*)&tmpulong, sizeof(long), 1, hp);
+	    if (FFI_BUF_SIGN(retval, long, long)) {
+		FFI_CHANGE_BUF_SIGN(retval, long, long, unsigned long);
+		res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, unsigned long, 1);
+	    } else {
+		res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, unsigned long, 0);
 	    }
         }
     } else if (rtype == &ffi_type_uchar) {
         /* It also applies for uint8 */
-        res = make_small(*((unsigned char*) retval));
+	res = FFI_NATIVE_TO_SMALL(retval, unsigned char, unsigned char);
     } else if (rtype == &ffi_type_schar) {
         /* It also applies for sint8 */
-        res = make_small(*((char*) retval));
+	res = FFI_NATIVE_TO_SMALL(retval, signed char, signed char);
     } else if (rtype == &ffi_type_uint16) {
-        res = make_small(*((Uint16*) retval));
+	res = FFI_NATIVE_TO_SMALL(retval, Uint16, Uint16);
     } else if (rtype == &ffi_type_sint16) {
-        res = make_small(*((Sint16*) retval));
+	res = FFI_NATIVE_TO_SMALL(retval, Sint16, Sint16);
     } else if (rtype == &ffi_type_uint32) {
-        res = erts_make_integer(*((Uint32*) retval), p);
+        res = erts_make_integer(FFI_BUF_VALUE(retval, Uint32, Uint32), p);
     } else if (rtype == &ffi_type_sint32) {
-        res = erts_make_signed_integer(*((Sint32*) retval), p);
+        res = erts_make_signed_integer(FFI_BUF_VALUE(retval, Uint32, Uint32),
+				       p);
     } else if (rtype == &ffi_type_uint64) {
-	tmpu64 = *((Uint64*)retval);
-	if (IS_USMALL(0, tmpu64)) {
-	    res = make_small(tmpu64);
+	if (FFI_BUF_IS_USMALL(retval, Uint64)) {
+	    res = FFI_NATIVE_TO_SMALL(retval, Uint64, Uint);
 	} else {
-#ifndef ARCH_64
-	    /* On 32-bit architectures, a 64-bit value that does not
-	     * fit in a small int may require a variable number of words. */
-	    if (tmpu64 <= (Uint64)UINT32_MAX) {
-		/* A 32-bit big integer is enough */
-		hp = ArithAlloc(p, 1 + WSIZE(sizeof(Uint32)));
-		tmpu32 = (Uint32)tmpu64;
-		res = bytes_to_big((byte*)&tmpu32, 4, 0, hp);
-	    } else {
-		/* A 64-bit big integer is necessary */
-		hp = ArithAlloc(p, 1 + WSIZE(sizeof(Uint64)));
-		res = bytes_to_big((byte*)&tmpu64, 8, 0, hp);
-	    }
-#else /* ARCH_64 */
-	    hp = ArithAlloc(p, 1 + WSIZE(sizeof(Uint64)));
-	    res = bytes_to_big((byte*)&tmpu64, 8, 0, hp);
-#endif
+	    res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, Uint64, 0);
 	}
     } else if (rtype == &ffi_type_sint64) {
-	tmps64 = *((Sint64*)retval);
-	if (IS_SSMALL(tmps64)) {
-	    res = make_small(tmps64);
+	if (FFI_BUF_IS_SSMALL(retval, Sint64)) {
+	    res = FFI_NATIVE_TO_SMALL(retval, Sint64, Uint);
 	} else {
-#ifndef ARCH_64
-	    /* On 32-bit architectures, a 64-bit value that does not
-	     * fit in a small int may require a variable number of words. */
-	    if (((tmps64 > 0) && (tmps64 <= (Sint64)UINT32_MAX))
-		|| ((tmps64 < 0) && (tmps64 >= -(Sint64)UINT32_MAX))) {
-		/* A 32-bit big integer is enough */
-		hp = ArithAlloc(p, 1 + WSIZE(sizeof(Sint32)));
-		if (tmps64 < 0) {
-		    tmpu32 = (Uint32)-tmps64;
-		    res = bytes_to_big((byte*)&tmpu32, 4, 1, hp);
-		} else {
-		    tmpu32 = (Uint32)tmps64;
-		    res = bytes_to_big((byte*)&tmpu32, 4, 0, hp);
-		}
+	    if (FFI_BUF_SIGN(retval, Sint64, Sint64)) {
+		FFI_CHANGE_BUF_SIGN(retval, Sint64, Sint64, Uint64);
+		res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, Uint64, 1);
 	    } else {
-		/* A 64-bit big integer is necessary */
-		hp = ArithAlloc(p, 1 + WSIZE(sizeof(Sint64)));
-		if (tmps64 < 0) {
-		    tmpu64 = (Uint64)-tmps64;
-		    res = bytes_to_big((byte*)&tmpu64, 8, 1, hp);
-		} else {
-		    res = bytes_to_big((byte*)&tmps64, 8, 0, hp);
-		}
+		res = FFI_UNSIGNED_NATIVE_TO_BIG(p, retval, Uint64, 0);
 	    }
-#else /* ARCH_64 */
-	    hp = ArithAlloc(p, 1 + WSIZE(sizeof(Sint64)));
-	    if (tmps64 < 0) {
-		tmpu64 = (Uint64)-tmps64;
-		res = bytes_to_big((byte*)&tmpu64, 8, 1, hp);
-	    } else {
-		res = bytes_to_big((byte*)&tmps64, 8, 0, hp);
-	    }
-#endif
 	}
     } else if (rtype == &ffi_type_longdouble) {
         /* Sorry, we must truncate the long double into a double */
diff -r 34b57ba8b406 -r 54b43754447d erts/emulator/beam/erl_bif_ffi_endianness.h
--- /dev/null
+++ b/erts/emulator/beam/erl_bif_ffi_endianness.h
@@ -0,0 +1,223 @@
+/* ``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 __ERL_BIF_FFI_ENDIANNESS_H__
+#define __ERL_BIF_FFI_ENDIANNESS_H__
+
+#ifdef HAVE_CONFIG_H
+#  include "config.h"
+#endif
+
+#ifdef HAVE_LIBFFI
+
+#include "erl_term.h"
+#include "sys.h"
+#include "big.h"
+
+/* 
+ * Helper macros for dealing with endianness FFI buffers.
+ *
+ * Only macros with the FFI_ prefix should be used outside of this
+ * file (see below).
+ *
+ * NOTE: here we use Uint assuming that it is a word-sized type.
+ */
+
+#define ERL_FFI_WORD_MASK (~((Uint)0))
+
+#if WORDS_BIGENDIAN
+/******************************************************************************
+ * BIGENDIAN PLATFORMS
+ *****************************************************************************/
+
+/* Given a word-aligned buffer large enough to contain a value of type
+ * ORIGTYPE, return the number of unused bytes (from the beginning of
+ * the buffer) that must be discarded when the buffer contents are
+ * casted to CTYPE */
+#define SUBVAL_OFFSET(ORIGTYPE, CTYPE)					\
+    ((sizeof(CTYPE) <= sizeof(ORIGTYPE))				\
+     ? ((sizeof(ORIGTYPE) > sizeof(Uint))				\
+	? (sizeof(ORIGTYPE) - sizeof(CTYPE))				\
+	: (sizeof(Uint) - sizeof(CTYPE)))				\
+     : 0)
+
+/* Copy a native buffer into a little-endian one, or vice versa */
+static inline void _copy_swap_native_le(byte *dest, const byte *src,
+					unsigned int size)
+{
+    unsigned int i = 0;
+
+    dest += size - 1;
+    for (; i < size; ++i) {
+	*dest-- = *src++;
+    }    
+}
+
+/* Copy the given number of bytes from an Erlang big integer to a
+ * native-endianness buffer. */
+static inline void _big_to_unsigned_native(byte *dest, Eterm big,
+					   unsigned int size) 
+{
+    byte buf[size];
+    unsigned int big_bytes = big_size(big) * sizeof(digit_t);
+    unsigned int pad = ((big_bytes < size)
+			? (size - big_bytes)
+			: 0);
+    
+    big_to_bytes(big, buf); 
+    /* Pad if the big size is lesser than the target type size */
+    _copy_swap_native_le(dest + pad, buf, size - pad);
+
+    /* Fill the padding (i.e. the MSBs) with 0 */
+    if (pad) {
+	memset(dest, 0, pad);
+    }
+}
+
+/* Copy a value of the given type from an Erlang big integer to a
+ * native-endianness buffer.  NOTE: the big sign will be ignored */
+#define FFI_BIG_TO_UNSIGNED_NATIVE(DEST, ETERM, CTYPE) \
+    _big_to_unsigned_native(((byte*)(DEST)), (ETERM), sizeof(CTYPE))
+
+#else /* !WORDS_BIGENDIAN */
+/******************************************************************************
+ * LITTLE-ENDIAN PLATFORMS
+ *****************************************************************************/
+
+#define SUBVAL_OFFSET(ORIGTYPE, CTYPE) 0
+
+/* Since we know that big integer bytes are still properly aligned on
+ * little-endian platforms, we can save a big_to_bytes() call */
+#define FFI_BIG_TO_UNSIGNED_NATIVE(DEST, ETERM, CTYPE)			\
+    {									\
+	*(CTYPE*)(DEST) = (CTYPE)0;					\
+	if ((big_size(ETERM) * sizeof(digit_t)) < sizeof(CTYPE)) {	\
+	    memcpy((DEST), big_v(ETERM), big_size(ETERM) * sizeof(digit_t)); \
+	} else {							\
+	    *(CTYPE*)(DEST) = *(CTYPE*)big_v(ETERM);			\
+	}								\
+    }
+
+#endif /* !WORDS_BIGENDIAN */
+
+/******************************************************************************
+ * ALMOST ENDIANNESS-INDEPENDANT MACROS
+ *****************************************************************************/
+
+/* Get the value of type CTYPE stored in a buffer of type BUFTYPE */
+#define FFI_BUF_VALUE(BUF, BUFTYPE, CTYPE)			\
+    *((CTYPE*)((BUF) + SUBVAL_OFFSET(BUFTYPE, CTYPE)))
+
+/* Check whether the native value contained in BUF (of type BUFTYPE)
+ * fits in an Erlang small integer (with sign) */
+#define FFI_BUF_IS_SSMALL(BUF, BUFTYPE)					\
+    IS_SSMALL(FFI_BUF_VALUE(BUF, BUFTYPE, BUFTYPE))
+
+/* Check whether the native value contained in BUF (of type BUFTYPE)
+ * fits in an Erlang small integer (without sign) */
+#define FFI_BUF_IS_USMALL(BUF, BUFTYPE)					\
+    IS_USMALL(0, FFI_BUF_VALUE(BUF, BUFTYPE, BUFTYPE))
+
+/* Create an Erlang small integer from a buffer (of type BUFTYPE)
+ * containing a native sub-value (of type CTYPE) */
+#define FFI_NATIVE_TO_SMALL(SRC, BUFTYPE, CTYPE)		\
+    make_small(FFI_BUF_VALUE(SRC, BUFTYPE, CTYPE))
+
+/* Check whether the sub-value (of type CTYPE) stored in the given
+ * buffer (of type BUFTYPE) is negative */
+#define FFI_BUF_SIGN(BUF, BUFTYPE, CTYPE)		\
+    (FFI_BUF_VALUE(BUF, BUFTYPE, CTYPE) < ((CTYPE)0))
+
+/* Change the sign of the native value (of type OLDTYPE) stored in BUF
+ * (of type BUFTYPE).  The sign change will perform a cast from
+ * OLDTYPE to NEWTYPE.  NOTE: OLDTYPE and NEWTYPE should have the same
+ * sizeof()s, in order to avoid overflows */
+#define FFI_CHANGE_BUF_SIGN(BUF, BUFTYPE, OLDTYPE, NEWTYPE)		\
+    {									\
+	FFI_BUF_VALUE(BUF, BUFTYPE, NEWTYPE) =				\
+	    -(FFI_BUF_VALUE(BUF, BUFTYPE, OLDTYPE));			\
+    }
+
+/* Create an Erlang big integer from the given native-endianness
+ * buffer, using the given sign.  NOTE: the native buffer is assumed
+ * to contain an unsigned value; also, the native value must actually
+ * require a big integer in order to be stored (the function caller is
+ * required to verify that this is the case) */
+static inline Eterm _unsigned_native_to_big(Process *p, byte *src,
+					    unsigned int size, int sign)
+{
+    Uint *ptr;
+    unsigned int words_count;
+    Eterm *hp;
+#if WORDS_BIGENDIAN
+    byte le_buf[size];
+#endif
+
+    ASSERT(size >= sizeof(Uint));
+    ASSERT(!(size & ((unsigned int)1)));
+
+    if (size == sizeof(Uint)) {
+	/* The caller is expected to check that a big integer is
+	 * actually needed, and a small integer is not enough */
+	ASSERT(!FFI_BUF_IS_USMALL(src, Uint));
+
+	/* A single-word big integer is enough */
+	hp = ArithAlloc(p, 1 + 1);
+#if WORDS_BIGENDIAN
+	_copy_swap_native_le(le_buf, src, size);
+	src = le_buf;
+#endif
+	return bytes_to_big(src, size, sign, hp);
+    }
+    
+    /* We need to count the number of words actually needed to
+     * store the native number */
+    words_count = (size / sizeof(Uint)) + ((size % sizeof(Uint))
+					   ? 1 : 0);
+#if WORDS_BIGENDIAN
+    for (ptr = (Uint*)src;
+	 !(*ptr & ERL_FFI_WORD_MASK);
+	 ++ptr, --words_count);
+#else
+    for (ptr = ((Uint*)src) + (words_count - 1);
+	 !(*ptr & ERL_FFI_WORD_MASK);
+	 --ptr, --words_count);
+#endif
+
+    hp = ArithAlloc(p, 1 + words_count);
+#if WORDS_BIGENDIAN
+    _copy_swap_native_le(le_buf, src + (size - (words_count * sizeof(Uint))),
+			 words_count * sizeof(Uint));
+    src = le_buf;
+#endif
+    return bytes_to_big(src, words_count * sizeof(Uint), sign, hp);
+}
+
+/* Create an Erlang big integer (with sign) from a buffer containing
+ * an unsigned native integer (of type BUFTYPE) */
+#define FFI_UNSIGNED_NATIVE_TO_BIG(PROCESS, SRC, BUFTYPE, SIGN)		\
+    _unsigned_native_to_big((PROCESS), ((byte*)(SRC)), sizeof(BUFTYPE), (SIGN))
+
+#endif /* HAVE_LIBFFI */
+
+#endif /* __ERL_BIF_FFI_ENDIANNESS_H__ */
