3.3 Foreign Function Interface


3.3.1 What is a FFI?

A Foreign Function Interface, or FFI for short, is a means for a programming language to interface with libraries written in other programming languages, the foreign code. You will see this concept most often being used in interpreted environments, such as Python, Ruby or Lisp, where one wants to reuse the big number of libraries written in C and C++ for dealing with graphical interfaces, networking, filesystems, etc.

A FFI is made of at least three components:

Foreign objects management

This is the data that the foreign code will use. A FFI needs to provide means to build and manipulate foreign data, with automatic conversions to and from lisp data types whenever possible, and it also has to deal with issues like garbage collection and finalization.

Foreign code loader

To actually use a foreign routine, the code must reside in memory. The process of loading this code and finding out the addresses of the routines we want to use is normally done by an independent component.

Foreign function invocation

This is the part of the FFI that deals with actually calling the foreign routines we want to use. For that one typically has to tell the FFI what are the arguments that these routines expect, what are the calling conventions and where are these routines to be found.

On top of these components sits a higher level interface written entirely in lisp, with which you will actually declare and use foreign variables, functions and libraries. In the following sections we describe both the details of the low-level components (See Two kinds of FFI and Foreign objects), and of the higher level interface (See Higher level interfaces). It is highly recommended that you read all sections.


3.3.2 Two kinds of FFI

ECL allows for two different approaches when building a FFI. Both approaches have a different implementation philosophy and affect the places where you can use the FFI and how.

Static FFI (SFFI)

For every foreign function and variable you might need to use, a wrapper is automatically written in C with the help of ffi:c-inline. These wrappers are compiled using an ordinary C compiler and linked against both the foreign libraries you want to use and against the ECL library. The result is a FASL file that can be loaded from ECL and where the wrappers appear as ordinary lisp functions and variables that the user may directly invoked.

Dynamic FFI (DFFI)

First of all, the foreign libraries are loaded in memory using the facilities of the operating system. Similar routines are used to find out and register the memory location of all the functions and variables we want to use. Finally, when actually accessing these functions, a little piece of assembly code does the job of translating the lisp data into foreign objects, storing the arguments in the stack and in CPU registers, calling the function and converting back the output of the function to lisp.

ECL for this purpose utilizes libffi, a portable foreign-function interface library.

figures/ffi

Figure 3.2: FFI components

As you see, the first approach uses rather portable techniques based on a programming language (C, C++) which is strongly supported by the operating system. The conversion of data is performed by a calling routines in the ECL library and we need not care about the precise details (organizing the stack, CPU registers, etc) when calling a function: the compiler does this for us.

On the other hand, the dynamic approach allows us to choose the libraries we load at any time, look for the functions and invoke them even from the toplevel, but it relies on unportable techniques and requires the developers to know very well both the assembly code of the machine the code runs on and the calling conventions of that particular operating system. For these reasons ECL doesn’t maintain it’s own implementation of the DFFI but rather relies on the third party library.

ECL currently supports the static method on all platforms, and the dynamical one a wide range of the most popular ones, shown in the section Supported Platforms at https://sourceware.org/libffi/.

You can test if your copy of ECL was built with DFFI by inspecting whether the symbol :dffi is present in the list from variable *features*.


3.3.3 Foreign objects

While the foreign function invocation protocols differ strongly between platforms and implementations, foreign objects are pretty easy to handle portably. For ECL, a foreign object is just a bunch of bytes stored in memory. The lisp object for a foreign object encapsulates several bits of information:

A foreign object may contain many different kinds of data: integers, floating point numbers, C structures, unions, etc. The actual type of the object is stored in a list or a symbol which is understood by the higher level interface (See Higher level interfaces).

The most important component of the object is the memory region where data is stored. By default ECL assumes that the user will perform manual management of this memory, deleting the object when it is no longer needed. The first reason is that this block may have been allocated by a foreign routine using malloc(), or mmap(), or statically, by referring to a C constant. The second reason is that foreign functions may store references to this memory which ECL is not aware of and, in order to keep these references valid, ECL should not attempt to automatically destroy the object.

In many cases, however, it is desirable to automatically destroy foreign objects once they have been used. The higher level interfaces UFFI and CFFI provide tools for doing this. For instance, in the following example adapted from the UFFI documentation, the string name is automatically deallocated

(ffi:def-function ("gethostname" c-gethostname)
  ((name (* :unsigned-char))
   (len :int))
  :returning :int)

(ffi:with-foreign-object (name '(:array :unsigned-char 256))
    (if (zerop (c-gethostname (ffi:char-array-to-pointer name) 256))
        (format t "Hostname: ~S" (ffi:convert-from-foreign-string name))
        (error "gethostname() failed.")))

3.3.3.1 C Reference

Function: cl_object ecl_make_foreign_data (cl_object tag, cl_index size, void *data)

Description

This function creates a Lisp “foreign object” that points to a C data. Use this function to pass a data from C to Lisp.

tag denotes the data type (See Primitive Types) size is a number of elements in data (or 0 for a raw pointer) data is a pointer to C data (either an object or an array)

The C macro ecl_make_pointer(pointer) expands to ecl_make_foreign_data(ECL_NIL, 0, (pointer)).

Function: void *ecl_foreign_data_pointer_safe(cl_object f)

Description

This function returns a C pointer for the given Lisp foreign object. Lisp foreign objects are constructed with functions ecl_make_foreign_data and ecl_allocate_foreign_data.

This data is a subject of the garbage collection (unlike lisp functions like si:allocate-foreign-object). This is because the data producer here is the "C world" and the data consumer is the "Lisp world".

Function: char *ecl_base_string_pointer_safe(cl_object f)

Description

This function returns a pointer to a simple base string f. If f is not a simple base string this function signals an error.

Function: cl_object ecl_null_terminated_base_string(cl_object s)

Description

Tries to coerce a string to a simple base string suitable for ecl_base_string_pointer_safe. This function may cons data.


3.3.4 Higher level interfaces

Up to now we have only discussed vague ideas about how a FFI works, but you are probably more interested on how to actually code all these things in lisp. You have here three possibilities:

In the following two subsections we will discuss two practical examples of using the native UFFI and the CFFI library.

UFFI example

The example below shows how to use UFFI in an application. There are several important ingredients:

#|
Build and load this module with (compile-file "uffi.lsp" :load t)
|#
;;
;; This toplevel statement notifies the compiler that we will
;; need this shared library at runtime. We do not need this
;; statement in windows or modern macOS.
;; The actually needed path to libm might be different on different systems.
;;
#-(or ming32 windows darwin)
(ffi:load-foreign-library "/usr/lib/libm.so")
;;
;; With this other statement, we import the C function sin(),
;; which operates on IEEE doubles.
;;
(ffi:def-function ("sin" c-sin) ((arg :double))
                  :returning :double)
;;
;; We now use this function and compare with the lisp version.
;;
(format t "~%Lisp sin:~t~d~%C sin:~t~d~%Difference:~t~d"
	(sin 1.0d0) (c-sin 1.0d0) (- (sin 1.0d0) (c-sin 1.0d0)))

CFFI example

The CFFI library is an independent project and it is not shipped with ECL. If you wish to use it you can go to their homepage, download the code and build it using ASDF.

CFFI differs slightly from UFFI in that functions may be used even without being declared beforehand.

#|
Build and load this module with (compile-file "cffi.lsp" :load t)
|#
;;
;; This toplevel statement notifies the compiler that we will
;; need this shared library at runtime. We do not need this
;; statement in windows or macOS.
;;
#-(or ming32 windows darwin)
(cffi:load-foreign-library "/usr/lib/libm.so")
;;
;; With this other statement, we import the C function sin(),
;; which operates on IEEE doubles.
;;
(cffi:defcfun ("sin" c-sin) :double '(:double))
;;
;; We now use this function and compare with the lisp version.
;;
(format t "~%Lisp sin:~t~d~%C sin:~t~d~%Difference:~t~d"
	(sin 1.0d0) (c-sin 1.0d0) (- (sin 1.0d0) (c-sin 1.0d0)))
;;
;; The following also works: no declaration!
;;
(let ((c-cos (cffi:foreign-funcall "cos" :double 1.0d0 :double)))
   (format t "~%Lisp cos:~t~d~%C cos:~t~d~%Difference:~t~d"
	(cos 1.0d0) c-cos (- (cos 1.0d0) c-cos)))

SFFI example (low level inlining)

To compare with the previous pieces of code, we show how the previous programs would be written using ffi:clines and ffi:c-inline.

#|
Build and load this module with (compile-file "ecl.lsp" :load t)
|#
;;
;; With this other statement, we import the C function sin(), which
;; operates on IEEE doubles. Notice that we include the C header to
;; get the full declaration.
;;
(defun c-sin (x)
  (ffi:clines "#include <math.h>")
  (ffi:c-inline (x) (:double) :double "sin(#0)" :one-liner t))
;;
;; We now use this function and compare with the lisp version.
;;
(format t "~%Lisp sin:~t~d~%C sin:~t~d~%Difference:~t~d"
	(sin 1.0d0) (c-sin 1.0d0) (- (sin 1.0d0) (c-sin 1.0d0)))

3.3.5 SFFI Reference

Reference

Special Form: ffi:clines c/c++-code*

Insert C declarations and definitions

c/c++-code

One or more strings with C definitions. Not evaluated.

returns

No value.

Description

This special form inserts C code from strings passed in the arguments directly in the file that results from compiling lisp sources. Contrary to ffi:c-inline, this function may have no executable statements, accepts no input value and returns no value.

The main use of ffi:clines is to declare or define C variables and functions that are going to be used later in other FFI statements. All statements from arguments are grouped at the beginning of the produced header file.

ffi:clines is a special form that can only be used in lisp compiled files as a toplevel form. Other uses will lead to an error being signaled, either at the compilation time or when loading the file.

Examples

In this example the ffi:clines statement is required to get access to the C function cos:

(ffi:clines "#include <math.h>")
(defun cos (x)
  (ffi:c-inline (x) (:double) :double "cos(#0)" :one-liner t))
Special Form: ffi:c-inline (lisp-values) (arg-c-types) return-type c/c++-code &key (side-effects t) (one-liner nil)

Inline C code in a lisp form

lisp-values

One or more lisp expressions. Evaluated.

arg-c-types

One or more valid FFI types. Evaluated.

return-type

Valid FFI type or (values ffi-type*).

c/c++-code

String containing valid C code plus some valid escape forms.

one-liner

Boolean indicating, if the expression is a valid R-value. Defaults to nil.

side-effects

Boolean indicating, if the expression causes side effects. Defaults to t.

returns

One or more lisp values.

Description

This is a special form which can be only used in compiled code and whose purpose is to execute some C code getting and returning values from and to the lisp environment.

The first argument lisp-values is a list of lisp forms. These forms are going to be evaluated and their lisp values will be transformed to the corresponding C types denoted by the elements in the list arg-c-types.

The input values are used to create a valid C expression using the template in C/C++-code. This is a string of arbitrary size which mixes C expressions with two kind of escape forms.

The first kind of escape form are made of a hash and a letter or a number, as in: #0, #1, ..., until #z. These codes are replaced by the corresponding input values. The second kind of escape form has the format @(return [n]), it can be used as lvalue in a C expression and it is used to set the n-th output value of the ffi:c-inline form.

When the parameter one-liner is true, then the C template must be a simple C statement that outputs a value. In this case the use of @(return) is not allowed. When the parameter one-liner is false, then the C template may be a more complicated block form, with braces, conditionals, loops and spanning multiple lines. In this case the output of the form can only be set using @(return).

Parameter side-effects set to false will indicate, that the functions causes no side-effects. This information is used by the compiler to optimize the resulting code. If side-effects is set to false, but the function may cause the side effects, then results are undefined.

Note that the conversion between lisp arguments and FFI types is automatic. Note also that ffi:c-inline cannot be used in interpreted or bytecompiled code! Such usage will signal an error.

Examples

The following example implements the transcendental function SIN using the C equivalent:

(ffi:c-lines "#include <math.h>")
(defun mysin (x)
  (ffi:c-inline (x) (:double) :double
    "sin(#0)"
    :one-liner t
    :side-effects nil))

This function can also be implemented using the @(return) form as follows:

(defun mysin (x)
  (ffi:c-inline (x) (:double) :double
    "@(return)=sin(#0);"
    :side-effects nil))

The following example is slightly more complicated as it involves loops and two output values:

(defun sample (x)
  (ffi:c-inline (x (+ x 2)) (:int :int) (values :int :int) "{
    int n1 = #0, n2 = #1, out1 = 0, out2 = 1;
    while (n1 <= n2) {
      out1 += n1;
      out2 *= n1;
      n1++;
    }
    @(return 0)= out1;
    @(return 1)= out2;
    }"
   :side-effects nil))
Special Form: ffi:c-progn args &body body

Interleave C statements with the Lisp code

args

Lisp arguments. Evaluated.

returns

No value.

Description

This form is used for it’s side effects. It allows for interleaving C statements with the Lisp code. The argument types doesn’t have to be declared – in such case the objects type in the C world will be cl_object.

Examples

(lambda (i)
  (let* ((limit i)
         (iterator 0)
         (custom-var (cons 1 2)))
    (declare (:int limit iterator))
    (ffi:c-progn (limit iterator custom-var)
                 "cl_object cv = #2;"
                 "ecl_print(cv, ECL_T);"
                 "for (#1 = 0; #1 < #0; #1++) {"
                 (format t "~&Iterator: ~A, I: ~A~%" iterator i)
                 "}")))
Special Form: ffi:defcallback name ret-type arg-desc &body body
name

Name of the lisp function.

ret-type

Declaration of the return type which function returns.

arg-desc

List of pairs (arg-name arg-type).

body

Function body.

returns

Pointer to the defined callback.

Description

Defines Lisp function and generates a callback for the C world, which may be passed to these functions. Note, that this special operator has also a dynamic variant (with the same name and interface).

Macro: ffi:defcbody name arg-types result-type c-expression

Define C function under the lisp name

name

Defined function name.

arg-types

Argument types of the defined Lisp function.

result-type

Result type of the C function (may be (values ...).

returns

Defined function name.

Description

The compiler defines a Lisp function named by name whose body consists of the C code of the string c-expression. In the c-expression one can reference the arguments of the function as #0, #1, etc.

The interpreter ignores this form.

Macro: ffi:defentry name arg-types c-name &key no-interrupts
name

Lisp name for the function.

arg-types

Argument types of the C function.

c-name

If c-name is a list, then C function result type is declared as (car c-name) and its name is (string (cdr c-name)).

If it’s an atom, then the result type is :object, and function name is (string c-name).

returns

Lisp function name.

Description

The compiler defines a Lisp function named by name whose body consists of a calling sequence to the C language function named by c-name.

The interpreter ignores this form.

Special Form: ext:with-backend &key bytecodes c/c++

Use different code depending on the backend.

Description

Depending on whether the bytecodes or C compiler is used, this form will emit the code given in the corresponding keyword argument.

Examples

CL-USER> (defmacro test ()
           '(ext:with-backend :c/c++ "c/c++" :bytecodes "bytecodes"))
TEST
CL-USER> (test)
"bytecodes"
CL-USER> (funcall (compile nil (lambda () (test))))

;;; OPTIMIZE levels: Safety=2, Space=0, Speed=3, Debug=3
"c/c++"

Macro: ffi:defla name args &body body

Provide Lisp alternative for interpreted code.

Description

Used to DEFine Lisp Alternative. For the interpreter, ffi:defla is equivalent to defun, but the compiler ignores this form.


3.3.6 DFFI Reference

Variable: ffi:*use-dffi*

This variable controls whether DFFI is used or not.


3.3.7 UFFI Reference


3.3.7.1 Primitive Types

Primitive types have a single value, these include characters, numbers, and pointers. They are all symbols in the keyword package.

:char
:unsigned-char

Signed/unsigned 8-bits. Dereferenced pointer returns a character.

:byte
:unsigned-byte

Signed/unsigned 8-bits. Dereferenced pointer returns an integer.

:short
:unsigned-short
:int
:unsigned-int
:long
:unsigned-long

Standard integer types (16-bit, 32-bit and 32/64-bit).

:int16-t
:uint16-t
:int32-t
:uint32-t
:int64-t
:uint64-t

Integer types with guaranteed bitness.

:float
:double

Floating point numerals (32-bit and 64-bit).

:long-double

Floating point numeral (usually 80-bit, at least 64-bit, exact bitness is compiler/architecture/platform dependent).

:csfloat
:cdfloat
:clfloat

Complex floating point numerals. These types exist only when ECL is built with c99complex support.

:cstring

A NULL terminated string used for passing and returning characters strings with a C function.

:void

The absence of a value. Used to indicate that a function does not return a value.

:pointer-void

Points to a generic object.

*

Used to declare a pointer to an object.

:object

A generic lisp object (i.e. a cl_object in C)

Reference

Macro: ffi:def-constant name value &key (export nil)

Binds a symbol to a constant.

name

A symbol that will be bound to the value.

value

An evaluated form that is bound the the name.

export

When t, the name is exported from the current package. Defaults to nil.

returns

Constant name.

Description

This is a thin wrapper around defconstant. It evaluates at compile-time and optionally exports the symbol from the package.

Examples

(ffi:def-constant pi2 (* 2 pi))
(ffi:def-constant exported-pi2 (* 2 pi) :export t)

Side Effects

Creates a new special variable.

Macro: ffi:def-foreign-type name definition

Defines a new foreign type

name

A symbol naming the new foreign type.

value

A form that is not evaluated that defines the new foreign type.

returns

Foreign type designator (value).

Description

Defines a new foreign type

Examples

(ffi:def-foreign-type my-generic-pointer :pointer-void)
(ffi:def-foreign-type a-double-float :double-float)
(ffi:def-foreign-type char-ptr (* :char))

Side effects

Defines a new foreign type.

Function: ffi:null-char-p char

Tests a character for NULL value

char

A character or integer.

returns

A boolean flag indicating if char is a NULL value.

Description

A predicate testing if a character or integer is NULL. This abstracts the difference in implementations where some return a character and some return a integer whence dereferencing a C character pointer.

Examples

(ffi:def-array-pointer ca :unsigned-char)
  (let ((fs (ffi:convert-to-foreign-string "ab")))
    (values (ffi:null-char-p (ffi:deref-array fs 'ca 0))
            (ffi:null-char-p (ffi:deref-array fs 'ca 2))))
;; => NIL T

3.3.7.2 Aggregate Types

Overview

Aggregate types are comprised of one or more primitive types.

Reference

Macro: ffi:def-enum name fields &key separator-string

Defines a C enumeration

name

A symbol that names the enumeration.

fields

A list of field definitions. Each definition can be a symbol or a list of two elements. Symbols get assigned a value of the current counter which starts at 0 and increments by 1 for each subsequent symbol. It the field definition is a list, the first position is the symbol and the second position is the value to assign the the symbol. The current counter gets set to 1+ this value.

returns

A string that governs the creation of constants. The default is "#".

Description

Declares a C enumeration. It generates constants with integer values for the elements of the enumeration. The symbols for the these constant values are created by the concatenation of the enumeration name, separator-string, and field symbol. Also creates a foreign type with the name name of type :int.

Examples

(ffi:def-enum abc (:a :b :c)) 
;; Creates constants abc#a (1), abc#b (2), abc#c (3) and defines
;; the foreign type "abc" to be :int

(ffi:def-enum efoo (:e1 (:e2 10) :e3) :separator-string "-")
;; Creates constants efoo-e1 (1), efoo-e2 (10), efoo-e3 (11) and defines
;; the foreign type efoo to be :int

Side effects

Creates a :int foreign type, defines constants.

Macro: ffi:def-struct name &rest fields

Defines a C structure

name

A symbol that names the structure.

fields

A variable number of field definitions. Each definition is a list consisting of a symbol naming the field followed by its foreign type.

Description

Declares a structure. A special type is available as a slot in the field. It is a pointer that points to an instance of the parent structure. It’s type is :pointer-self.

Examples

(ffi:def-struct foo (a :unsigned-int) 
  (b    (* :char)) 
  (c    (:array :int 10)) 
  (next :pointer-self))

Side effects

Creates a foreign type.

Function: ffi:get-slot-value obj type field

Retrieves a value from a slot of a structure

obj

A pointer to the foreign structure.

type

The name of the foreign structure.

field

The name of the desired field in the foreign structure.

returns

The value of the field in the structure obj.

Description

Accesses a slot value from a structure. This is generalized and can be used with setf.

Examples

(ffi:get-slot-value foo-ptr 'foo-structure 'field-name)
(setf (ffi:get-slot-value foo-ptr 'foo-structure 'field-name) 10)
Function: ffi:get-slot-pointer obj type field

Retrieves a pointer from a slot of a structure

obj

A pointer to the foreign structure.

type

The name of the foreign structure.

field

The name of the desired field in the foreign structure.

returns

The value of the pointer field in the structure obj.

Description

This is similar to ffi:get-slot-value. It is used when the value of a slot is a pointer type.

Examples

(ffi:get-slot-pointer foo-ptr 'foo-structure 'my-char-ptr)
Macro: ffi:def-array-pointer name type

Defines a pointer to an array of type

name

A name of the new foreign type.

type

The foreign type of the array elements.

Description

Defines a type that is a pointer to an array of type.

Examples

(ffi:def-array-pointer byte-array-pointer :unsigned-char)

Side effects

Defines a new foreign type.

Function: ffi:deref-array array type position

Dereference an array

array

A foreign array.

type

The foreign type of the array.

position

An integer specifying the position to retrieve from the array.

returns

The value stored in the position of the array.

Description

Dereferences (retrieves) the value of the foreign array element. setf-able.

Examples

(ffi:def-array-pointer ca :char)
  (let ((fs (ffi:convert-to-foreign-string "ab")))
    (values (ffi:null-char-p (ffi:deref-array fs 'ca 0))
    (ffi:null-char-p (ffi:deref-array fs 'ca 2))))
;; => NIL T
Macro: ffi:def-union name &rest fields

Defines a foreign union type

name

A name of the new union type.

fields

A list of fields of the union in form (field-name field-type).

Description

Defines a foreign union type.

Examples

(ffi:def-union test-union
  (a-char :char)
  (an-int :int))

(let ((u (ffi:allocate-foreign-object 'test-union)))
  (setf (ffi:get-slot-value u 'test-union 'an-int) (+ 65 (* 66 256)))
  (prog1
     (ffi:ensure-char-character (ffi:get-slot-value u 'test-union 'a-char))
   (ffi:free-foreign-object u)))
;; => #\A

Side effects

Defines a new foreign type.


3.3.7.3 Foreign Objects

Overview

Objects are entities that can allocated, referred to by pointers, and can be freed.

Reference

Function: ffi:allocate-foreign-object type &optional size

Allocates an instance of a foreign object

type

The type of foreign object to allocate. This parameter is evaluated.

size

An optional size parameter that is evaluated. If specified, allocates and returns an array of type that is size members long. This parameter is evaluated.

returns

A pointer to the foreign object.

Description

Allocates an instance of a foreign object. It returns a pointer to the object.

Examples

(ffi:def-struct ab (a :int) (b :double))
;; => (:STRUCT (A :INT) (B :DOUBLE))
(ffi:allocate-foreign-object 'ab)
;; => #<foreign AB>
Function: ffi:free-foreign-object ptr

Frees memory that was allocated for a foreign object

ptr

A pointer to the allocated foreign object to free.

Description

Frees memory that was allocated for a foreign object.

Macro: ffi:with-foreign-object (var type) &body body

Wraps the allocation, binding and destruction of a foreign object around a body of code

var

Variable name to bind.

type

Type of foreign object to allocate. This parameter is evaluated.

body

Code to be evaluated.

returns

The result of evaluating the body.

Description

This function wraps the allocation, binding, and destruction of a foreign object around the body of code.

Examples

(defun gethostname2 ()
  "Returns the hostname"
  (ffi:with-foreign-object (name '(:array :unsigned-char 256))
    (if (zerop (c-gethostname (ffi:char-array-to-pointer name) 256))
        (ffi:convert-from-foreign-string name)
        (error "gethostname() failed."))))
Macro: ffi:size-of-foreign-type ftype

Returns the number of data bytes used by a foreign object type

ftype

A foreign type specifier. This parameter is evaluated.

returns

Number of data bytes used by a foreign object ftype.

Description

Returns the number of data bytes used by a foreign object type. This does not include any Lisp storage overhead.

Examples

(ffi:size-of-foreign-type :unsigned-byte)
;; => 1
(ffi:size-of-foreign-type 'my-100-byte-vector-type)
;; => 100
Function: ffi:pointer-address ptr

Returns the address of a pointer

ptr

A pointer to a foreign object.

returns

An integer representing the pointer’s address.

Description

Returns the address as an integer of a pointer.

Function: ffi:deref-pointer ptr ftype

Dereferences a pointer

ptr

Pointer to a foreign object.

ftype

Foreign type of the object being pointed to.

returns

The value of the object where the pointer points.

Description

Returns the object to which a pointer points. setf-able.

Notes

Casting of the pointer may be performed with ffi:with-cast-pointer together with ffi:deref-pointer/ffi:deref-array.

Examples

(let ((intp (ffi:allocate-foreign-object :int)))
  (setf (ffi:deref-pointer intp :int) 10)
  (prog1
      (ffi:deref-pointer intp :int)
    (ffi:free-foreign-object intp)))
;; => 10
Function: ffi:ensure-char-character object

Ensures that a dereferenced :char pointer is a character

object

Either a character or a integer specifying a character code.

returns

A character.

Description

Ensures that an objects obtained by dereferencing :char and :unsigned-char pointers is a lisp character.

Examples

(let ((fs (ffi:convert-to-foreign-string "a")))
  (prog1 
      (ffi:ensure-char-character (ffi:deref-pointer fs :char))
    (ffi:free-foreign-object fs)))
;; => #\a

Exceptional Situations

Depending upon the implementation and what UFFI expects, this macro may signal an error if the object is not a character or integer.

Function: ffi:ensure-char-integer object

Ensures that a dereferenced :char pointer is an integer

object

Either a character or a integer specifying a character code.

returns

An integer.

Description

Ensures that an objects obtained by dereferencing :char and :unsigned-char pointers is a lisp integer.

Examples

(let ((fs (ffi:convert-to-foreign-string "a")))
  (prog1 
      (ffi:ensure-char-integer (ffi:deref-pointer fs :char))
    (ffi:free-foreign-object fs)))
;; => 96

Exceptional Situations

Depending upon the implementation and what UFFI expects, this macro may signal an error if the object is not a character or integer.

Function: ffi:make-null-pointer ftype

Create a NULL pointer of a specified type

ftype

A type of object to which the pointer refers.

returns

The NULL pointer of type ftype.

Function: ffi:null-pointer-p ptr

Tests a pointer for NULL value

ptr

A foreign object pointer.

returns

The boolean flag.

Variable: ffi:+null-cstring-pointer+

A NULL cstring pointer. This can be used for testing if a cstring returned by a function is NULL.

Macro: ffi:with-cast-pointer (var ptr ftype) &body body

Wraps a body of code with a pointer cast to a new type

var

Symbol which will be bound to the casted object.

ptr

Pointer to a foreign object.

ftype

A foreign type of the object being pointed to.

returns

The value of the object where the pointer points.

Description

Executes body with ptr cast to be a pointer to type ftype. var will be bound to this value during the execution of body.

Examples

(ffi:with-foreign-object (size :int)
  ;; FOO is a foreign function returning a :POINTER-VOID
  (let ((memory (foo size)))
    (when (mumble)
      ;; at this point we know for some reason that MEMORY points
      ;; to an array of unsigned bytes
      (ffi:with-cast-pointer (memory :unsigned-byte)
        (dotimes (i (deref-pointer size :int))
          (do-something-with
              (ffi:deref-array memory '(:array :unsigned-byte) i)))))))
Macro: ffi:def-foreign-var name type module

Defines a symbol macro to access a variable in foreign code

name

A string or list specifying the symbol macro’s name. If it is a string, that names the foreign variable. A Lisp name is created by translating #\_ to #\- and by converting to upper-case.

If it is a list, the first item is a string specifying the foreign variable name and the second it is a symbol stating the Lisp name.

type

A foreign type of the foreign variable.

module

Either a string specifying the module (or library) the foreign variable resides in, :default if no module needs to be loaded or nil to use SFFI.

Description

Defines a symbol macro which can be used to access (get and set) the value of a variable in foreign code.

Examples

C code defining foreign structure, standalone integer and the accessor:

int baz = 3;

typedef struct {
  int x;
  double y;
} foo_struct;

foo_struct the_struct = { 42, 3.2 };

int foo () {
  return baz;
}

Lisp code defining C structure, function and a variable:

(ffi:def-struct foo-struct
  (x :int)
  (y :double))

(ffi:def-function ("foo" foo) ()
  :returning :int
  :module "foo")

(ffi:def-foreign-var ("baz" *baz*) :int "foo")
(ffi:def-foreign-var ("the_struct" *the-struct*) foo-struct "foo")

*baz*           ;; => 3
(incf *baz*)    ;; => 4
(foo)           ;; => 4

3.3.7.4 Foreign Strings

Overview

UFFI has functions to two types of C-compatible strings: cstrings and foreign strings. cstrings are used only as parameters to and from functions. In some implementations a cstring is not a foreign type but rather the Lisp string itself. On other platforms a cstring is a newly allocated foreign vector for storing characters. The following is an example of using cstrings to both send and return a value.

(ffi:def-function ("getenv" c-getenv) 
    ((name :cstring))
  :returning :cstring)

(defun my-getenv (key)
  "Returns an environment variable, or NIL if it does not exist"
  (check-type key string)
  (ffi:with-cstring (key-native key)
    (ffi:convert-from-cstring (c-getenv key-native))))

In contrast, foreign strings are always a foreign vector of characters which have memory allocated. Thus, if you need to allocate memory to hold the return value of a string, you must use a foreign string and not a cstring. The following is an example of using a foreign string for a return value.

(ffi:def-function ("gethostname" c-gethostname)
    ((name (* :unsigned-char))
     (len :int))
  :returning :int)

(defun gethostname ()
  "Returns the hostname"
  (let* ((name (ffi:allocate-foreign-string 256))
         (result-code (c-gethostname name 256))
         (hostname (when (zerop result-code)
                     (ffi:convert-from-foreign-string name))))
    ;; UFFI does not yet provide a universal way to free
    ;; memory allocated by C's malloc. At this point, a program
    ;; needs to call C's free function to free such memory.
    (unless (zerop result-code)
      (error "gethostname() failed."))))

Foreign functions that return pointers to freshly allocated strings should in general not return cstrings, but foreign strings. (There is no portable way to release such cstrings from Lisp.) The following is an example of handling such a function.

(ffi:def-function ("readline" c-readline)
    ((prompt :cstring))
  :returning (* :char))

(defun readline (prompt)
  "Reads a string from console with line-editing."
  (ffi:with-cstring (c-prompt prompt)
    (let* ((c-str (c-readline c-prompt))
           (str (ffi:convert-from-foreign-string c-str)))
      (ffi:free-foreign-object c-str)
      str)))

Reference

Macro: ffi:convert-from-cstring object

Converts a cstring to a Lisp string

object

A cstring

returns

A Lisp string

Description

Converts a Lisp string to a cstring. This is most often used when processing the results of a foreign function that returns a cstring.

Macro: ffi:convert-to-cstring object

Converts a Lisp string to a cstring

object

A Lisp string

returns

A cstring

Description

Converts a Lisp string to a cstring. The cstring should be freed with ffi:free-cstring.

Side Effects

This function allocates memory.

Macro: ffi:convert-from-cstring cstring

Free memory used by cstring

cstring

cstring to be freed.

Description

Frees any memory possibly allocated by ffi:convert-to-cstring. On ECL, a cstring is just the Lisp string itself.

Macro: ffi:with-cstring (cstring string) &body body

Binds a newly created cstring

cstring

A symbol naming the cstring to be created.

string

A Lisp string that will be translated to a cstring.

body

The body of where the cstring will be bound.

returns

Result of evaluating the body.

Description

Binds a symbol to a cstring created from conversion of a string. Automatically frees the cstring.

Examples

(ffi:def-function ("getenv" c-getenv) 
    ((name :cstring))
  :returning :cstring)

(defun getenv (key)
  "Returns an environment variable, or NIL if it does not exist"
  (check-type key string)
  (ffi:with-cstring (key-cstring key)
    (ffi:convert-from-cstring (c-getenv key-cstring))))
Macro: ffi:with-cstrings bindings &body body

Binds a newly created cstrings

bindings

List of pairs (cstring string), where cstring is a name for a cstring translated from Lisp string string.

body

The body of where the bindings will be bound.

returns

Result of evaluating the body.

Description

Binds a symbols to a cstrings created from conversion of a strings. Automatically frees the cstrings. This macro works similar to let*. Based on with-cstring.

Macro: ffi:convert-from-foreign-string foreign-string &key length (null-terminated-p t)

Converts a foreign string into a Lisp string

foreign-string

A foreign string.

length

The length of the foreign string to convert. The default is the length of the string until a NULL character is reached.

null-terminated-p

A boolean flag with a default value of t. When true, the string is converted until the first NULL character is reached.

returns

A Lisp string.

Description

Returns a Lisp string from a foreign string. Can translate ASCII and binary strings.

Macro: ffi:convert-to-foreign-string string

Converts a Lisp string to a foreign string

string

A Lisp string.

returns

A foreign string.

Description

Converts a Lisp string to a foreign string. Memory should be freed with ffi:free-foreign-object.

Macro: ffi:allocate-foreign-string size &key unsigned

Allocates space for a foreign string

size

The size of the space to be allocated in bytes.

unsigned

A boolean flag with a default value of t. When true, marks the pointer as an :unsigned-char.

returns

A foreign string which has undefined contents.

Description

Allocates space for a foreign string. Memory should be freed with ffi:free-foreign-object.

Macro: ffi:with-foreign-string (foreign-string string) &body body

Binds a newly allocated foreign-string

foreign-string

A symbol naming the foreign string to be created.

string

A Lisp string that will be translated to a foreign string.

body

The body of where the foreign-string will be bound.

returns

Result of evaluating the body.

Description

Binds a symbol to a foreign-string created from conversion of a string. Automatically deallocates the foreign-string.

Examples

Macro: ffi:with-foreign-strings bindings &body body

Binds a newly created foreign string

bindings

List of pairs (foreign-string string), where foreign-string is a name for a foreign string translated from Lisp string string.

body

The body of where the bindings will be bound.

returns

Result of evaluating the body.

Description

Binds a symbols to a foreign-strings created from conversion of a strings. Automatically frees the foreign-strings. This macro works similar to let*. Based on ffi:with-foreign-string.


3.3.7.5 Functions and Libraries

Reference

Macro: ffi:def-function name args &key module (returning :void) (call :cdecl)
name

A string or list specifying the function name. If it is a string, that names the foreign function. A Lisp name is created by translating #\_ to #\- and by converting to upper-case in case-insensitive Lisp implementations. If it is a list, the first item is a string specifying the foreign function name and the second it is a symbol stating the Lisp name.

args

A list of argument declarations. If nil, indicates that the function does not take any arguments.

module

Either a string specifying which module (or library) that the foreign function resides, :default if no module needs to be loaded or nil to use SFFI.

call

Function calling convention. May be one of :default, :cdecl, :sysv, :stdcall, :win64 and :unix64.

This argument is used only when we’re using the dynamic function interface. If ECL is built without the DFFI support, then it uses SFFI the call argument is ignored.

returning

A declaration specifying the result type of the foreign function. :void indicates that the function does not return any value.

Description

Declares a foreign function.

Examples

(ffi:def-function "gethostname"
    ((name (* :unsigned-char))
     (len :int))
  :returning :int)
Macro: ffi:load-foreign-library filename &key module supporting-libraries force-load system-library
filename

A string or pathname specifying the library location in the filesystem.

module

IGNORED A string designating the name of the module to apply to functions in this library.

supporting-libraries

IGNORED A list of strings naming the libraries required to link the foreign library.

force-load

IGNORED Forces the loading of the library if it has been previously loaded.

system-library

Denotes if the loaded library is a system library (accessible with the correct linker flags). If t, then SFFI is used and the linking is performed after compilation of the module. Otherwise (default) both SFFI and DFFI are used, but SFFI only during the compilation.

returns

A generalized boolean true if the library was able to be loaded successfully or if the library has been previously loaded, otherwise nil.

Description

Loads a foreign library. Ensures that a library is only loaded once during a session.

Examples

(ffi:load-foreign-library #p"/usr/lib/libmagic.so.1")
;; => #<codeblock "/usr/lib/libmagic.so">

Side Effects

Loads the foreign code into the Lisp system.

Affected by

Ability to load the file.

Function: ffi:find-foreign-library names directories &key drive-letters types

Finds a foreign library file

names

A string or list of strings containing the base name of the library file.

directories

A string or list of strings containing the directory the library file.

drive-letters

A string or list of strings containing the drive letters for the library file.

types

A string or list of strings containing the file type of the library file. Default is nil. If nil, will use a default type based on the currently running implementation.

returns

A path containing the path to the first file found, or nil if the library file was not found.

Description

Finds a foreign library by searching through a number of possible locations. Returns the path of the first found file.

Examples

(ffi:find-foreign-library '("libz" "libmagic")
                          '("/usr/local/lib/" "/usr/lib/")
                          :types '("so" "dll"))
;; => #P"/usr/lib/libz.so.1.2.8"