Git Product home page Git Product logo

cl-autowrap's Introduction

Now with libffi!

Using its own facilities, autowrap now includes autowrap/libffi. This allows functions that pass and return structs to be called using autowrap. To use this, just load or :depends-on cl-autowrap/libffi instead of cl-autowrap:

  :depends-on (... :cl-autowrap/libffi ...)
  ...

Of course, this requires libffi be compiled and available to your lisp.

Usage mostly identical; functions called via libffi look and act the same as any others. The one exception is functions that return a struct by value:

(c-with ((return-value some-struct))
  (some-call-returning-some-struct return-value ...))

Calls returning a struct take the return as their first parameter. This should be evident in SLIME/Sly. This ultimately allows easier management of freeing as well as more control over where they're stored. (They also still return the value, if you're trying to chain calls.)

Issues?

If you have issues, do not hesitate to file an issue! See the FAQ for some quick tips.

cl-autowrap

This is a new c2ffi-based wrapper generator for Common Lisp with a focus, performance, convenience, and completeness. It works like this:

(c-include "file.h")

That's it. This calls c2ffi and generates architecture-specific .spec files you can distribute with your project. Neither c2ffi, nor any compiler (or even .h files!) are necessary for your users!

  • Types: structs (including bitfields!), unions, enums, typedefs, etc.
  • Wrappers: Thin wrappers for structs, unions, and aliases of structs and unions: pointers and validation only, no expensive translation
  • Accessors: Complete recursive accessors for structs and unions, including anonymous struct members, arrays, and pointers for each field.
  • Functions: Macros which expand into foreign calls via CFFI-SYS
  • Metadata: Full access to all the information about all types, functions, etc.

For instance:

/* test.h - abbreviated from example */
typedef struct foo {
  int a, b;
  char c[3];

  struct {
    unsigned int b0 : 2, b1 : 3;

    struct {
      char x, y;
    } s;
  } x[2];
} foo_t;

foo_t* get_foo();
void free_foo(foo_t *foo);
int* get_int();

Out of this, we can do the following. (Note: dots are just part of the function names for disambiguation, this doesn't alter the reader):

(c-include "test.h")

(let ((foo (get-foo)))
  (setf (foo-t.a foo) 5)             ;; foo.a = 5;
  (setf (foo-t.x[].b0 foo 0) #b10)   ;; foo.x[0].b0 = 2;
  (print (foo-t.x[].s.x foo 1))      ;; anonymous struct
  (foo-t.x[].s foo 0)                ;; => child wrapper
  (foo-t.x[].s& foo 0)               ;; &(foo.x[0].s) => pointer
  (free-foo foo))

Alternatively, there is now cl-plus-c, which can optionally be loaded for a different access mechanism and much quicker compile times:

(asdf:load-system :cl-plus-c)
(use-package :plus-c)

;;; This allocates a FOO-T and frees it at the end:
(c-let ((foo foo-t :free t))
  (print foo)                        ;; => wrapper
  (setf (foo :a) 5)                  ;; foo.a = 5;
  (setf (foo :x 0 :b0) #b10)         ;; foo.x[0].b0 = 2;
  (print (foo :x 1 :s :x))           ;; anonymous struct: foo.x[1].s.x
  (foo :x 0 :s)                      ;; => child wrapper
  (foo :x 0 :s &))                   ;; &(foo.x[0].s) => pointer

See cl-plus-c.md for more information.

Overview

Using cl-autowrap is meant to get you to the "lispifying" stage of your wrapper as quickly and conveniently as possible:

  • Make sure you have c2ffi
  • Load your library as you normally would with CFFI
  • Make a file for your c-include
  • Examine wrappers and tweak if necessary
  • Back to lisp!

c2ffi

You will need to build c2ffi if you have not already done so. This requires a repository version of LLVM and Clang, but the build process is straightforward.

Again, note that your users do not need this, assuming you distribute the .spec files appropriate to their architecture. cl-autowrap should generate everything for you, though.

If you decide not to install c2ffi, you can specify its path directly by setting autowrap:*c2ffi-program*, e.g.:

(setf autowrap:*c2ffi-program* "/path/to/my/c2ffi")

This should be part of your local configuration; do not set this in code you distribute. This includes LET forms around C-INCLUDE.

Loading Libraries

This should be done normally with CFFI. Either the high-level interface with CFFI:DEFINE-FOREIGN-LIBRARY and CFFI:USE-FOREIGN-LIBRARY or the low-level interface with CFFI-SYS:%LOAD-FOREIGN-LIBRARY work.

Writing the c-include

It's highly recommended that you use a separate package and file for cl-autowrap. The reasons are simple:

  • A lot of symbols will be generated without regard.
  • Many symbols will also be exported.
  • A rather large number of functions and structs will be generated, resulting in a hefty compile time. With a separate file, this only needs to happen once.

(In fact, you can now specify individual packages for each set of symbols that are generated. See below.)

Once you have this, you can write a simple c-include. This must be a top-level statement:

(c-include "somefile.h")

This will look for somefile.h and generate .spec files in *default-pathname-defaults*, which is probably not very helpful! To fix this, use the following:

(c-include (function-that-finds "somefile.h")
           :spec-path #P"/path/to/spec")

(Note that while these parameters are eval'd, this happens at compile time, so if you use a *special-variable*, its definition needs surrounded by an EVAL-WHEN.)

Hardcoded paths and reinventing functionality aren't very nice though; In both cases you can specify a complete "ASDF path" (starting with the system name), and it'll query the path from ASDF. For example, if we have an ASDF system called my-wrapper, we can do the following:

(c-include '(my-wrapper some-module "localfile.h")
           :spec-path '(my-wrapper spec-module))

Assuming you had defined "localfile.h" as a :static-file of some-module in my-wrapper, as well as spec-module, everything would work as intended.

This is especially useful because you can have a single local header that includes all the files you wish to wrap, and those will be found by c2ffi in the standard include paths.

Tweaking

While c2ffi and cl-autowrap do quite a lot, there are a few times where you may want to or be required to intervene. You can look at any errors that occur, or the symbols that are exported, or even simply macroexpand the c-include and examine the output.

By default, c2ffi outputs everything and likewise cl-autowrap imports everything. Thus you get a rather large sampling of libc where you probably don't need it. Thus you may want to exclude some definitions. You can do this in two ways:

(c-include "file.h"
           :exclude-sources ("/path/to/source1"
                             "/path/.*source2" ...)
           :exclude-definitions ("SomeFunc1"
                                 "_suffix$"))

The first, :exclude-sources, looks at the source information generated by c2ffi for each definition. This is an easy way to exclude the majority of irrelevant definitions. You can make exceptions to this list via :include-sources:

(c-include "file.h"
           :exclude-sources ("/path/to/source1"
                             "/path/.*source2" ...)
           :include-sources ("/path/to/source1/but-include-this"))

While everything else matching "/path/to/source1" will be excluded, in this example, definitions in "/path/to/source1/but-include-this" will still be included (if they exist).

The next specifier, :exclude-definitions, excludes specific definitions by name. These may be conflicting or unnecessary. For instance, SDL2 includes a number of functions ending in _inline and some functions which use stdargs, all of which are unnecessary (or unusable).

Both of these use cl-ppcre regular expressions to match, thus you have a great deal of flexibility with a few strings.

You may also wish to simply rename some symbols. The default routine generally translates symbols like you want, but you may occasionally find C functions named in a way that breaks this. The default rules are as follows:

  • XYZFooBar => XYZ-FOO-BAR
  • foo_barBaz => FOO-BAR-BAZ
  • _x_y => _X_Y (because I think -X-Y looks worse)

However if you encounter something like "FOObar", it is likely you want "FOO-BAR", not "FO-OBAR", which is what you would get. Thus you can specify an exception:

(c-include "file.h"
           :symbol-exceptions (("FOObar" . "FOO-BAR") ...))

These are simple, case-sensitive string matches and replacements. The replacement is interned exactly, so if you specify lowercase here, you will get a symbol with lowercase characters.

There is also a more complex cl-ppcre-based match and replace facility:

(c-include "file.h"
           :symbol-regex (("^MATCH_string" (PARAMS)
                            (lambda (string matches regex) ..
                               NEW-STRING))))

Using this facility, you may specify regex-function pairs. PARAMS specifies further parameters to PPCRE:CREATE-SCANNER, e.g., :case-insensitive-mode. If a symbol matches the given regex, the function will be called with the string, any substring matches, and the original regex (in case you want to further apply it). You must return a string, which will then be converted by the above rules into a final string.

This should usually be unnecessary. The use case for its creation was handling names that vary unpredictably only by case:

CLUTTER_KEY_OMEGA
CLUTTER_KEY_omega
CLUTTER_KEY_THORN
CLUTTER_KEY_Thorn
CLUTTER_KEY_Adiaeresis
CLUTTER_KEY_adiaeresis

In this situation, the more complicated regex-function matching is necessary.

Alternatively, as was actually decided for the above clutter case, since there was "no rhyme or reason" to the naming scheme of the #define'd constants, one may filter constant names to be interned, opting, instead, for referencing them through a separate constant-accessor macro:

(c-include "file.h"
            :exclude-constants (".*")
            :constant-accessor clutter-constant)
;; Access constants like this:
(clutter-constant "CLUTTER_Z")
(clutter-constant "CLUTTER_z")

By default all "known" architectures (at the time of writing, windows, mac, linux on i686 and x86_64) are generated by default. This may not always work; for instance, one architecture may require header files your system lacks. You can exclude it using the following:

(c-include "file.h"
           :exclude-arch ("i686-pc-win32" ...))

This will exclude that target triple from being generated and causing a warning or output if it fails.

You can also specify individual packages for symbol exports. This can be useful if, for instance, you wish to import all accessors, or all functions, or similar, while not necessarily importing everything:

(c-include "file.h"
           :definition-package PACKAGE
           :function-package PACKAGE
           :wrapper-package PACKAGE
           :accessor-package PACKAGE
           :constant-package PACKAGE
           :extern-package PACKAGE)
  • :definition-package PACKAGE: All "definition" symbols, which include type names and function names (not to be confused with function macros which you use in your code)
  • :function-package PACKAGE: All "function" symbols, which are all macros expanding to foreign calls
  • :wrapper-package PACKAGE: All "wrapper" symbols, which are all structs generated to wrap foreign record types
  • :accessor-package PACKAGE: All "accessor" symbols, which are all functions generated to access record fields
  • :constant-package PACKAGE: All "constant" symbols, which are all +symbols+ representing C constants
  • :extern-package PACKAGE: All "extern" symbols, which are all symbols (which are symbol-macros) representing C extern symbols

Wrappers and FFI

At this point you probably have definitions generated (or are hopefully submitting a question or bug report!). But how to use them?

While cl-autowrap uses CFFI, it almost exclusively uses the low-level CFFI-SYS interface. It does not use the high-level type translation interface, or even cffi:defcfun. Pointers are still whatever your Lisp provides.

Instead, cl-autowrap defines a "new" higher-level interface I call SFFI, for "simplified FFI". While CFFI's high-level interface is nice for manually defining types and functions, it proves difficult when trying to automatically generate things or exercise precise control over various things like field layout.

You should never have to deal with SFFI directly, but all the fine-grained type information is available should you require access. This is occasionally useful. See below in the SFFI section for details.

However, you cannot use CFFI constructs from another wrapper directly with SFFI-defined functions, or vice versa, but you can always use pointers between the two.

Functions

cl-autowrap defines macros which wrap C calls with a few helpful features:

  • Wrappers (see below) or pointers are accepted for any pointer-to-struct (or union)
  • Symbols or integers are accepted for any enum
  • Lisp strings will be temporarily converted to C strings, then freed, for char* or unsigned char*. (If you need these to persist, you must provide your own pointer!)
  • For char* and unsigned char* returns, both a lisp string and a pointer are returned as VALUES, so you can free the pointer if necessary. You may prevent this conversion, and receive only the pointer, if you wrap the call in INHIBIT-STRING-CONVERSION:
(inhibit-string-conversion (function-returning-string ...))
  ;; => pointer

Otherwise, the call will be like any C call; there is no other type translation. In my experience, all but the most trivial C functions benefit from some wrapping, so this shouldn't be a big issue.

However, see "Other Features" below for some other helpful features, such as bitmasks.

Wrappers

Instead of merely returning pointers, cl-autowrap defines very thin wrappers for non-atomic named types. Wrappers are structs which contain two things:

  • A pointer, which is accessible with AUTOWRAP:PTR
  • A VALID-P field, which is used for storing pointer validity, and can be checked by AUTOWRAP:VALID-P

Wrappers are extremely useful for "safely" managing pointers, and are meant to be safe and "pretty" enough for users of your wrapper to use directly. Any dereference using PTR automatically checks validity, and you can use finalizers to clean them up. Note however that this is up to you: cl-autowrap merely provides the facility, nothing else. See "Garbage Collection and Wrappers" below.

Additionally, cl-autowrap generates a correct "type hierarchy", as much as such applies to C:

struct x { ... };
typedef struct x y;

Results in:

(defstruct (x (:include wrapper)))
(defstruct (y (:include x)))

This ensures type compatibility where the C side may arbitrarily specify compatible type aliases.

You may also obtain a "child" wrapper for a struct which is a field in another struct, using accessors:

struct foo_t {
   :
   struct { int a, b; } x;
};
(let* ((foo (get-foo-somehow))
       (x (foo-t.x foo)))
  :
  :
  ... )

This keeps a reference to the parent. These may also be safely dereferenced using AUTOWRAP:PTR, and checked using AUTOWRAP:VALID-P. Because there is a reference is kept to the parent, even if a reference is discarded by the user, the child is still safe to use.

Garbage Collection and Wrappers

One of the primary motivators behind wrappers is the ability to easily garbage collect C data. However, this still requires some care. To this end, the AUTOCOLLECT macro has been added; see below.

First, nothing besides checking is done automatically. Pointers are assumed valid when they are returned and made into wrappers. Any further invalidation and garbage collection must be handled by the one writing the wrapper.

Important: Absolutely no effort is made to keep wrappers unique or manage duplicates. Again: YOU CAN HAVE DUPLICATE WRAPPERS AND THIS CAN LEAD TO BAD THINGS. Generally this should only occur if you obtain the same pointer from a C API multiple times, such as a function which returns a global context pointer. It is up to you to handle this. Beware.

Once you are aware of this, you can use something like trivial-garbage to free pointers when you need:

(defun lispy-get-thing ()
  (let* ((thing (get-thing))
         (ptr (autowrap:ptr thing)))
    (tg:finalize thing (lambda () (free-thing ptr)))
    thing))

Note as as always to never reference the object, only the pointer, in the finalizer, or it will never be collected.

It is often useful to free things when you still have a reference. In this case, the pointer becomes invalid, and this is also handled by WRAPPER:

(defun lispy-free-thing (thing)
  (unwind-protect (free-thing thing)
    (tg:cancel-finalization thing)
    (autowrap:invalidate thing)))

In this case, further attempts to dereference THING via AUTOWRAP:PTR will result in an INVALID-WRAPPER error.

You may be tempted to do this:

(defun bad-free-thing (thing)
  (tg:cancel-finalization thing)
  (autowrap:invalidate thing)
  (free-thing thing))

Unfortunately, since you invalidated THING, when you pass it to FREE-THING, it will be invalid ... resulting in an error.

Never manage "child" wrapper objects. This probably goes without saying, but they're tied to the parent object, and not meant to be managed separately.

Also, you may be tempted to do this, to avoid "dangling pointers":

(defun terrible-get-thing ()
  (let* ((thing (get-thing))
         (ptr (autowrap:ptr thing)))
    (tg:finalize thing
      (lambda ()
        (free-thing ptr)
        (setf (autowrap:wrapper-ptr thing)
              (cffi:null-pointer))))
    thing))

This is both wrong and silly: there is a reference to THING in the finalizer, so it will never get freed. And if you had gotten here normally, there would be no references, so nothing would have the dangling pointer!

To facilitate doing this correctly, the AUTOCOLLECT macro has been added:

(autocollect (&optional PTR) WRAPPER-FORM &body) => WRAPPER-FORM-RESULT

If you are using trivial-garbage, this will extract the pointer from WRAPPER-FORM and call tg:finalize on the wrapper. The body forms should use POINTER to free the object. If you are not using trivial-garbage, it will produce an error.

For instance:

(autocollect (pointer)
    (get-thing)
  (free-thing pointer)) ;; => THING-WRAPPER

This will call GET-THING and finalize the resulting wrapper with the body. POINTER is the pointer; this defaults to the symbol PTR.

This is not fool-proof. Things to watch out for:

  • If you reference the wrapper, and not the pointer, it will never be collected.
  • If you try to autocollect a child wrapper, you will probably crash.
  • If you provide a function to manually free resources, you must use tg:cancel-finalization or this finalizer will still be called, likely double-freeing the memory and crashing.
  • It's still up to you to call something to free the pointer.

Accessors

Having wrappers and functions are nice, but getting at the data is important too. Accessors are generated recursively (up to a depth of 5, barring recursive types) for highly convenient access. From the top:

typedef struct foo {
  int a, b;
  char c[3];

  struct {
    unsigned int b0 : 2, b1 : 3;

    struct {
      char x, y;
    } s;
  } x[2];
} foo_t;

Accessors are named starting with their type name (in this case, FOO and FOO-T), followed by fields, separated by dots. There is no reader magic here: these are functions with dots as part of the name. (Dots were used mostly for disambiguation; if only dashes were used, name collision would be probable, since underscores are converted to dashes by default.)

The following special cases are available:

  • type.foo in the case of foo being a record type (struct or union), will return a child wrapper.
  • type.foo in the case of foo being a pointer will return the pointer
  • type.foo& will return a pointer to the field, not a wrapper, regardless of the type of foo. If foo is a pointer, then you get a pointer-pointer. This is just the same as &(x.foo) in C. This does not exist for bitfields.
  • type.foo* will dereference foo where foo is a pointer to a well-defined type, including record fields. E.g., type.foo*.bar; there is no type.foo.bar.
  • type.foo[] references an array element, where foo is declared as an array (not just as a pointer). Array indices are specified in order after the object: (type.foo[].bar[] obj i0 i1) is the equivalent of C's obj.foo[i0].bar[i1].

Additionally, SETF can set almost any field. The exceptions are any accessor which dereferences a record (i.e. returns a child wrapper), or is suffixed with &.

Bitfields are supported under the assumption that they are packed LSB-to-MSB on little endian and MSB-to-LSB on big endian architectures. If you actually encounter a problem with this, file a bug report with full details: the architecture, OS, lisp, C compiler, and an example struct. Theoretical possibilities are not considered bugs.

Note that bitfield operations cannot be done atomically and may not be done field-atomically (that is, you may have to lock the entire struct). Additionally, you cannot take the address of a bitfield. However, you can get information from SFFI metadata, or simply using the convenience function AUTOWRAP:BITFIELD-MASK.

Other Features

cl-autowrap has a number of other features that have not been discussed:

  • Allocation
  • Enums
  • Bitmasks
  • Callbacks
  • SFFI metadata and functions

Allocation

Since autowrap implements its own higher-level constructs over lower-level CFFI, you can't use CFFI's FOREIGN-ALLOC or similar functions and macros to easily allocate foreign records. Thus there are new constructs for doing so:

(let ((thing (autowrap:alloc 'type)))
  :
  (autowrap:free thing))

As you might expect, ALLOC will allocate memory of sufficient size for TYPE, and FREE will free it (and invalidate the wrapper for you). Note that if you are doing garbage collection as above, this does NOT remove finalizers for you: you MUST take care of this yourself where applicable.

There are also macros which will help with temporary allocation:

(with-alloc (thing 'type)
   :
   :
   )

This will take care of allocation and freeing within the block. You should not use finalizers here. If you try to reference the value outside of the scope of the block, it will be invalid. If you wish to allocate multiple objects and free them, you can use the following:

(with-many-alloc ((thing1 'type1)
                  (thing2 'type2)
                  :
                   )
  :
  )

Note that while any typedef type aliases can be referenced simply by symbol as in C, record types are called (:struct (NAME)) or (:union (NAME)), and also like C, you must write this out if there is no type alias for NAME. For example:

struct X { ... };
typedef struct Y { ... } Y;

int main() {
    struct X foo;    /* No type alias */
    Y bar;           /* Type alias */
}
(with-many-alloc ((foo '(:struct (X))) ;; No type alias
                  (bar 'Y))            ;; Type alias
    :
    )

Arrays

In addition to single objects, autowrap also allows allocation and reference to arrays of objects. This is less safe, however: there are no provisions for bounds-checking, since the data is simply not there. (While in theory, we could add size data on the lisp side, this is a false sense of security, since you will often be dealing arrays from C.)

Allocation methods all take an optional COUNT parameter:

(alloc x 'type 3)

(with-alloc (x 'type 5) ...)

(with-many-alloc ((x 'type 5)
                  (y 'type 2))
  ...)

To reference these, you can use C-APTR and C-AREF:

(c-aptr x 1) ;; => raw pointer
(c-aref y 2) ;; => wrapper

Unfortunately, this may present some performance issues, since unlike record accessors, the type must be looked up at runtime. In theory, autowrap could generate array accessors for all types, but this would vastly increase the number of accessors generated with little value, since most will not be used.

Instead, you may specify the type explicitly:

(c-aptr x 1 'type) ;; => pointer
(c-aptr y 2 'type) ;; => wrapper

In this case, as long as 'type is constant-p, the compiler macro should expand it at compile-time.

Basic C types (e.g., :int, :char, etc) are also supported; in this case, a wrapper is not returned, but the value itself:

(c-aref x 1 :int) ;; => number

You can also set array members for basic types only:

(setf (c-aref x 1 :int) 10)

In both of these cases, since autowrap does not provide additional wrappers for basic types, you must specify the type explicitly.

Enums

Enums are imported and created as types, but they're typically used by specifying a keyword:

enum E {
  FOO_X, FOO_Y, FOO_Z
};

void fun(E);
(fun :x)

As you can see, common prefixes are eliminated and the symbols are interned as keywords. Additionally, functions taking enum symbols can also take numbers:

(fun 1)

You can also find the value or keyword for an enum as follows:

(autowrap:enum-key '(:enum (enum-name)) :key)
(autowrap:enum-value '(:enum (enum-name)) 1)

An actual AUTOWRAP:FOREIGN-ENUM can be used in place of 'enum-name if desired; otherwise it will be looked up via AUTOWRAP:FIND-TYPE.

Bitmasks

Bitmasks aren't actually a type in C, and are often defined as constants instead of enums or similar. Therefore, there is no real automatic way to determine a bitmask. Thus cl-autowrap provides a number of convenience facilities for doing this:

(autowrap:define-bitmask 'NAME
  '((:key1 . #x0001)
     :
      ...))

This defines a bitmask called NAME, which is separate from other C types, and can be used with the MASK function:

(some-function (autowrap:mask 'NAME :key1 :key5))

This also has a compiler macro which will expand to an integer constant if the value can be determined at compile-time.

Additionally, to aid in converting predefined constants to bitmasks, there is the following macro, which expands to an AUTOWRAP:DEFINE-BITMASK call:

(autowrap:define-bitmask-from-constants (name)
  +some-foo+
  +some-bar+
  +some-baz+)

This essentially expands to the following:

(autowrap:define-bitmask 'name
  (list `(:foo . ,+some-foo+)
        `(:bar . ,+some-bar+)
        `(:baz . ,+some-baz+)))

Callbacks

Autowrap now provides a thin layer on top of CFFI-SYS:%DEFCALLBACK:

(autowrap:defcallback NAME RETURN-TYPE
    ((PARAM TYPE)
     ...)
  ...)

The main difference is that you may specify SFFI type aliases as parameters, since these are not available to the higher-level CFFI:DEFCALLBACK.

Additionally, there is the following:

(autowrap:callback 'name)

This simply expands to CFFI-SYS:%CALLBACK, but is provided for convenience.

SFFI Metadata and Functions

This is not fully-documented at the moment, but full access to metadata and definition functions is available. For instance:

(autowrap:find-type '(:struct (struct-name)))

This will return the object that represents struct struct_name, or nil. If nothing else, it should be fairly easy to inspect this value and look at fields, types, etc. Accessors are exported for all types (or should be); see package.lisp for a complete list.

These values can certainly be useful when doing various tricky things with C data, and it's also certainly possible to manually write definitions for every type and generate lisp functions, though for records (i.e. struct and union), this requires explicitly specifying bit sizes and field layouts. While probably not directly useful (or necessary) for importing C types, these could be useful for generating similar definitions via other means than c2ffi.

Copying

This is licensed under the BSD 2-Clause license.

cl-autowrap's People

Contributors

anthonyf avatar attila-lendvai avatar borodust avatar cbaggers avatar clsd avatar cmushawn avatar deepfire avatar dg1sbg avatar digikar99 avatar fitzsim avatar kpoeck avatar nagy avatar noloop avatar oldk1331 avatar robgssp avatar rpav avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

cl-autowrap's Issues

Reporting of skipped records

During compilation cl-autowrap reports skipped records:

; compiling (AUTOWRAP:C-INCLUDE (QUOTE #) ...); Note: skipping record
                                              ; :struct #:ANON-TYPE-4
                                              ; field :__POS of type
                                              ; __OFF64_T due to undefined
                                              ; foreign type: __OFF64_T
; Total of 0 compile-time skipped definitions
; Total of 1 compile-time missing entities:
;   __OFF64_T

It would be helpful for debugging if this note would include the name of the
file that introduced that record (esp. useful for anon-types).

Having some trouble running functions...

I'm in the process of wrapping nuklear and I thought i was good to go but after writing a small test function it barfs at me saying that it can't run functions.

function:

(defun test ()
  (c-with ((ctx nk-ffi:nk-context)
         (lay nk-ffi:nk-panel))
    (format t "Pre: Context ~A; Panel ~A~%" ctx lay)
    (format t "Addresses: ctx ~A lay ~A~%" (ctx &) (lay &))
    (finish-output)
    (nk-begin (ctx &) (lay &) "Demo"
                            (nk-rect 50 50 210 250)
                            (logior nk-ffi:+nk-window-border+
                                    nk-ffi:+nk-window-movable+
                                    nk-ffi:+nk-window-scalable+
                                    nk-ffi:+nk-window-minimizable+
                                    nk-ffi:+nk-window-title+))
    (format t "Post: Context ~A; Panel ~A~%" ctx lay)
    (nk-end ctx)))

error:

$ cl.ccl
Welcome to Clozure Common Lisp Version 1.11-r16635  (LinuxX8664)!

CCL is developed and maintained by Clozure Associates. For more information
about CCL visit http://ccl.clozure.com.  To enquire about Clozure's Common Lisp
consulting services e-mail [email protected] or visit http://www.clozure.com.

? (ql:quickload :nuklear)
To load "nuklear":
  Load 1 ASDF system:
    nuklear
; Loading "nuklear"
Value: 0
Pointer: #<A Foreign Pointer #x7FC6EC0244A0>
Value: 42
; Total of 0 load-time skipped definitions
; Total of 0 load-time missing entities

(:NUKLEAR)
? (nuklear:test)
Pre: Context #<NK-CONTEXT {#X7FC6EC0249D0}>; Panel #<NK-PANEL {#X7FC6EC0239C0}>
Addresses: ctx #<A Foreign Pointer #x7FC6EC0249D0> lay #<A Foreign Pointer #x7FC6EC0239C0>
> Error: Call-by-value not implemented yet for NK-FFI::NK-BEGIN
> While executing: NUKLEAR:TEST, in process listener(1).
> Type :POP to abort, :R for a list of available restarts.
> Type :? for other options.
1 >

And whats weird is that nk-begin shouldn't be in the nk-ffi package but nk-ffi.fns. Everything else seems to work fine and I'm basing my code off of the other autowrapped packages you've built, so I'm confused.

The full code is here: https://github.com/serialhex/cl-nuklear and it's barebones as I'm building it up, but I wanted to get it working before I get it finished...

Thanks in advance!

Compilation of cl-sdl2 fails in autowrap.lisp on ARM (Raspberry Pi2 + Linux) with CCL 1.10-r16196

When trying to compile SDL2 I ran into following error:

Invoking restart: Retry compiling #<CL-SOURCE-FILE "sdl2" "autowrap">.
> Error: #<CODE-VECTOR #x15A8D3FE> can't be destructured against the lambda list (AUTOWRAP::NAME AUTOWRAP::C-SYMBOL &KEY AUTOWRAP::VARIADIC-P &ALLOW-OTHER-KEYS), because it does not contain at least 2 elements.
> While executing: CCL::PREPARE-TO-DESTRUCTURE, in process listener(1).
> Type :GO to continue, :POP to abort, :R for a list of available restarts.
> If continued: Skip loading "crawler.lisp"
> Type :? for other options.
1 > 

With SBCL it will compile nicely, however starting any cl-sdl2 up on ARM will fail with SBCL because of lack of thread support.
If I can provide more infos or test something else, please let me know.

Structure type miswrapping

Actors:

  • clutter/clutter-types.h, which defines ClutterColor as:
  • typedef struct _ClutterColor ClutterColor;
  • clutter/clutter-color.h, which includes clutter/clutter-types.h, and defines
  • struct _ClutterColor, which has actual content -- four per-component guint8's
  • the spec file, which misrepresents struct _ClutterColor as having zero fields

Setting:

clutter/clutter-types.h

typedef struct _ClutterColor                    ClutterColor;

clutter/clutter-color.h

#include <clutter/clutter-types.h>
....
struct _ClutterColor
{
  /*< public >*/
  guint8 red;
  guint8 green;
  guint8 blue;

  guint8 alpha;
};

clutter-raw.x86_64-pc-linux-gnu.spec

{ "tag": "struct", "name": "_ClutterColor", "id": 0, "location": "/usr/include/clutter-1.0/clutter/clutter-types.h:80:16", "bit-size": 0, "bit-alignment": 0, "fields": [] },
{ "tag": "typedef", "name": "ClutterColor", "location": "/usr/include/clutter-1.0/clutter/clutter-types.h:80:49", "type": { "tag": ":struct", "name": "_ClutterColor", "id": 0 } },

Calling/invoking a function pointer

This might be just a documentation request:

I'm wrapping a structure that contains function pointers

struct my_struct {
...
  char* (*get_name)(my_struct* self);
  int (*get_id)(my_struct* self);
...
}

Give a (wrapped) pointer to such a struct, how would I call the callback functions, preferably without
having to generate accessors.

Argument X is not a REAL: NIL

Hi.
I'm trying to wrap libdrm. Here is where autowrap stucks:

Argument X is not a REAL: NIL
   [Condition of type SIMPLE-TYPE-ERROR]

Restarts:
 0: [RETRY] Retry SLIME REPL evaluation request.
 1: [*ABORT] Return to SLIME's top level.
 2: [ABORT] abort thread (#<THREAD "new-repl-thread" RUNNING {10078B2363}>)

Backtrace:
  0: (SB-KERNEL:TWO-ARG-> NIL 0)
      Locals:
        SB-DEBUG::ARG-0 = NIL
        SB-DEBUG::ARG-1 = 0
  1: (SB-VM::GENERIC->)
      [No Locals]
  2: (AUTOWRAP:DEFINE-FOREIGN-ENUM #:ANON-TYPE-1279 NIL ((:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3)))
      Locals:
        SB-DEBUG::ARG-0 = #:ANON-TYPE-1279
        SB-DEBUG::ARG-1 = NIL
        SB-DEBUG::ARG-2 = ((:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3))
  3: (AUTOWRAP::%ENSURE-TYPE (AUTOWRAP::ENUM (NIL :ID 23) (:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3)) "record ~(~S~) ~S field ~S of type ~S" (:STRUCT DRM-CONTROL :FUNC (..
      Locals:
        SB-DEBUG::ARG-0 = (AUTOWRAP::ENUM (NIL :ID 23) (:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3))
        SB-DEBUG::ARG-1 = "record ~(~S~) ~S field ~S of type ~S"
        SB-DEBUG::ARG-2 = (:STRUCT DRM-CONTROL :FUNC (AUTOWRAP::ENUM (NIL :ID 23) (:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3)))
  4: (AUTOWRAP::PARSE-RECORD-FIELDS :STRUCT DRM-CONTROL ((:FUNC (AUTOWRAP::ENUM # # # # #) :BIT-SIZE 32 :BIT-OFFSET 0 ...) (:IRQ :INT :BIT-SIZE 32 :BIT-OFFSET 32 ...)))
      Locals:
        SB-DEBUG::ARG-0 = :STRUCT
        SB-DEBUG::ARG-1 = DRM-CONTROL
        SB-DEBUG::ARG-2 = ((:FUNC (AUTOWRAP::ENUM (NIL :ID 23) (:ADD-COMMAND . 0) (:RM-COMMAND . 1) (:INST-HANDLER . 2) (:UNINST-HANDLER . 3)) :BIT-SIZE 32 :BIT-OFFSET 0 ...) (:IRQ :INT :BIT-SIZE 32 :BIT-OFFSET 32 ...))
  5: ((LAMBDA NIL :IN AUTOWRAP:DEFINE-FOREIGN-RECORD))
  6: (AUTOWRAP::CALL-WITH-WRAP-ATTEMPT DRM-CONTROL #<CLOSURE (LAMBDA NIL :IN AUTOWRAP:DEFINE-FOREIGN-RECORD) {10081B23CB}> "record (~A (~S))" (:STRUCT DRM-CONTROL))

Here is a piece of code which causes this condition:

struct drm_control {
    enum {
        DRM_ADD_COMMAND,
        DRM_RM_COMMAND,
        DRM_INST_HANDLER,
        DRM_UNINST_HANDLER
    } func;
    int irq;
};

And respective JSON code, generated by autowrap:

{ "tag": "struct",
  "ns": 0,
  "name": "drm_control",
  "id": 0,
  "location": "/usr/include/libdrm/drm.h:164:8",
  "bit-size": 64,
  "bit-alignment": 32,
  "fields": [{ "tag": "field",
           "name": "func",
           "bit-offset": 0,
           "bit-size": 32,
           "bit-alignment": 32,
           "type": { "tag": "enum",
                     "ns": 1936876800,
             "name": "",
             "id": 23,
             "location": "/usr/include/libdrm/drm.h:165:2",
             "fields": [{ "tag": "field",
                      "name": "DRM_ADD_COMMAND",
                      "value": 0 },
                    { "tag": "field",
                      "name": "DRM_RM_COMMAND",
                      "value": 1 },
                    { "tag": "field",
                      "name": "DRM_INST_HANDLER",
                      "value": 2 },
                    { "tag": "field",
                      "name": "DRM_UNINST_HANDLER",
                      "value": 3 }] } },
             { "tag": "field",
           "name": "irq",
           "bit-offset": 32,
           "bit-size": 32,
           "bit-alignment": 32,
           "type": { "tag": ":int",
                     "bit-size": 32,
             "bit-alignment": 32 } }] },

{ "tag": "enum",
  "ns": 24,
  "name": "",
  "id": 23,
  "location": "/usr/include/libdrm/drm.h:165:2",
  "fields": [{ "tag": "field",
           "name": "DRM_ADD_COMMAND",
           "value": 0 },
         { "tag": "field",
           "name": "DRM_RM_COMMAND",
           "value": 1 },
         { "tag": "field",
           "name": "DRM_INST_HANDLER",
           "value": 2 },
         { "tag": "field",
           "name": "DRM_UNINST_HANDLER",
           "value": 3 }] },

Errors while autowrapping Chipmunk2D

I'm trying to autowrap Chipmunk2D (https://github.com/slembcke/Chipmunk2D). I'm trying to build it on OS X.

I had an error where <float.h> couldn't be found. I searched the path where the Chipmunk2D XCode project finds float.h (/Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/lib/clang/6.1.0/include/) and added it to :sysincludes.

After solving that there are still many errors, but they all repeat. Basically, I have two types of errors:

CL-USER> (ql:quickload :cl-chipmunk)
To load "cl-chipmunk":
  Load 1 ASDF system:
    cl-chipmunk
; Loading "cl-chipmunk"
In file included from /var/folders/dv/8hnn7n357pq1g40tqsd9pk940000gn/T/TEMP-N8LQ13WQ:1:
In file included from /Users/simon/projects/cl-chipmunk/src/spec/chipmunk.h:1:
In file included from /usr/local/include/chipmunk/chipmunk.h:53:
In file included from /usr/local/include/chipmunk/chipmunk_types.h:45:
In file included from /System/Library/Frameworks/ApplicationServices.framework/Headers/ApplicationServices.h:23:
In file included from /System/Library/Frameworks/CoreServices.framework/Headers/CoreServices.h:19:
In file included from /System/Library/Frameworks/CoreFoundation.framework/Headers/CoreFoundation.h:55:
In file included from /System/Library/Frameworks/CoreFoundation.framework/Headers/CFPropertyList.h:13:
In file included from /System/Library/Frameworks/CoreFoundation.framework/Headers/CFStream.h:15:
In file included from /usr/include/dispatch/dispatch.h:51:
/usr/include/dispatch/object.h:143:15: error: blocks support disabled - compile with -fblocks or pick a deployment target that supports them
typedef void (^dispatch_block_t)(void);
              ^
In file included from /var/folders/dv/8hnn7n357pq1g40tqsd9pk940000gn/T/TEMP-N8LQ13WQ:1:
In file included from /Users/simon/projects/cl-chipmunk/src/spec/chipmunk.h:1:
In file included from /usr/local/include/chipmunk/chipmunk.h:53:
In file included from /usr/local/include/chipmunk/chipmunk_types.h:45:
In file included from /System/Library/Frameworks/ApplicationServices.framework/Headers/ApplicationServices.h:23:
In file included from /System/Library/Frameworks/CoreServices.framework/Headers/CoreServices.h:23:
In file included from /System/Library/Frameworks/CoreServices.framework/Frameworks/AE.framework/Headers/AE.h:20:
In file included from /System/Library/Frameworks/CoreServices.framework/Frameworks/CarbonCore.framework/Headers/CarbonCore.h:127:
In file included from /System/Library/Frameworks/CoreServices.framework/Frameworks/CarbonCore.framework/Headers/DriverServices.h:26:
In file included from /System/Library/Frameworks/CoreServices.framework/Frameworks/CarbonCore.framework/Headers/MachineExceptions.h:22:
In file included from /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/lib/clang/6.1.0/include/emmintrin.h:31:
In file included from /Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/lib/clang/6.1.0/include/xmmintrin.h:31:
/Applications/Xcode.app/Contents/Developer/Toolchains/XcodeDefault.xctoolchain/usr/lib/clang/6.1.0/include/mmintrin.h:46:12: error: invalid conversion between vector type '__m64' (vector of 1 'long long' value) and integer type 'int' of different size
    return (__m64)__builtin_ia32_vec_init_v2si(__i, 0);
           ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

The invalid conversion error occurs a lot for different types, but they all seem to come from emmintrin.h, xmmintrin.h and mmintrin.h. Same for the blocks support disabled error.

I would like to follow the instructions of the compiler for the blocks error, but I don't know how to pass those compiler options to cl-autowrap.

I would really appreciate it if you could give me some guidance ;)

Thank you!

ffi funcall expands into non-hygienic code

the ffi funcall expansion contains variable bindings with the name that is used in the original ffi function definition. the with this problem is that their value is expressions from user code, so these variables can have surprising interference with user code, unless their name is gensym'ed.

`autowrap:enum-key` not working

It looks like autowrap:enum-key doesn't work as documented.

(autowrap:enum-key 'log-level 1)

Note: skipping map value 1 of enum LOG-LEVEL to value due to
undefined foreign type: LOG-LEVEL
   [Condition of type AUTOWRAP:UNDEFINED-FOREIGN-TYPE-CONTEXTUALISED]

Looking at the code, enum-key calls require-type which calls
find-type which consults *foreign-types*, a hash whose keys are lists.
Even stranger, the entries for enums look like (:enum (enum-name)).

Wrapping gdk-pixbuf..

Good day Ryan!

I'm trying to wrap more stuff, this time GDK-Pixbuf + Clutter.
The bigger problem, is that without certain ignores, GDK-Pixbuf does not
get wrapped at all - none of its symbols appear in the spec files.
The smaller problem is that some glib types do not get wrapped no matter what ignores,
for instance the g* types -- gboolean, guint* etc.

The overall problem is that I feel ill-equipped for deduction of what goes
wrong, and why c2ffi chooses to omit something from its spec files..

Here is what I have (alternatively, check out [email protected]:deepfire/cffi-clutter.git):

clutter-raw.h

#include <glib.h>
#include <gdk-pixbuf/gdk-pixbuf.h>
#include <clutter/clutter.h>
#include <cogl/cogl.h>
#include <GL/gl.h>

clutter-raw.lisp

(cl:eval-when (:compile-toplevel :load-toplevel :execute)
  (cffi-sys:%load-foreign-library
   :libclutter "/usr/lib64/libgdk_pixbuf-2.0.so")
  (cffi-sys:%load-foreign-library
   :libclutter "/usr/lib64/libglib-2.0.so")
  (cffi-sys:%load-foreign-library
   :libclutter "/usr/lib64/libclutter-1.0.so.0"))

(autowrap:c-include "clutter-raw.h"
                    :exclude-arch ("i686-pc-linux-gnu"
                                   "i686-pc-win32"
                                   "x86_64-pc-win64"
                                   "i686-apple-darwin9"
                                   "x86_64-apple-darwin9")
                    :exclude-sources ("/usr/local/lib/clang/3.3/include/(?!stddef.h).*"
                                      ;; this (your) ignore weirdly enables GDK-Pixbuf wrapping
                                      ;; -- take it away, and none of its functions will appear in spec files.
                                      "/usr/include/(?!stdint.h|bits/types.h|sys/types.h|glib-2.0|clutter-1.0|cogl).*"
                                      "/usr/include/glib-2.0/glib/deprecated")
                    :sysincludes '("/usr/include/"
                                   "/usr/include/glib-2.0"
                                   "/usr/lib64/glib-2.0/include"
                                   "/usr/include/cairo"
                                   "/usr/include/cogl"
                                   "/usr/include/clutter-1.0"
                                   "/usr/include/pango-1.0"
                                   "/usr/include/atk-1.0"
                                   "/usr/include/gdk-pixbuf-2.0"
                                   "/usr/include/json-glib-1.0")
                    :exclude-constants (".*")
                    :constant-accessor const)

Make C2FFI optional

I would like cl-autowrap to generate bindings using a pre-existing spec file. So that I can run my software on systems without c2ffi. (I can't compile it on a Fedora 19)

Problem with calling ioctl

I think the code for the variadic argument of an ioctl call isn't properly passed through the macros.

My goal is to replace libusb with pure lisp. I managed to parse the ioctl constant definitions with the following code:

(ql:quickload :cl-autowrap)
(eval-when (:compile-toplevel :execute :load-toplevel)
  (defparameter *spec-path* (merge-pathnames "stage/sb-look-ma-no-libusb/"
                         (user-homedir-pathname))))

(progn
  (with-open-file (s "/tmp/usb0.h"
             :direction :output
             :if-does-not-exist :create
             :if-exists :supersede)
    (format s "#include \"/usr/include/linux/usbdevice_fs.h\"~%"))
  (autowrap::run-check autowrap::*c2ffi-program*
               (autowrap::list "/tmp/usb0.h"
                       "-D" "null"
                       "-M" "/tmp/usb_macros.h"
                       "-A" "x86_64-pc-linux-gnu"
                       ))


  (with-open-file (s "/tmp/usb1.h"
             :direction :output
             :if-does-not-exist :create
             :if-exists :supersede)

    (format s "#include <sys/types.h>~%")
    (format s "#include <sys/stat.h>~%")
    (format s "#include <sys/ioctl.h>~%")
    (format s "#include \"/tmp/usb0.h\"~%")
    (format s "#include \"/tmp/usb_macros.h\"~%")))

(autowrap:c-include "/tmp/usb1.h"
            :spec-path *spec-path*
            :exclude-arch ("arm-pc-linux-gnu"
                   "i386-unknown-freebsd"
                   "i686-apple-darwin9"
                   "i686-pc-linux-gnu"
                   "i686-pc-windows-msvc"
                   "x86_64-apple-darwin9"
                    ;"x86_64-pc-linux-gnu"
                   "x86_64-pc-windows-msvc"
                   "x86_64-unknown-freebsd")
            :exclude-sources ("/usr/include/linux/types.h"
                      "/usr/include/linux/magic.h")
            :include-sources ("/usr/include/linux/ioctl.h")
            :trace-c2ffi t)
(defun usb-control-msg (fd requesttype request value index buffer &key (timeout-ms 1000))
  (declare (type (unsigned-byte 8) requesttype request)
       (type (unsigned-byte 16) value index)
       (type (unsigned-byte 32) timeout-ms))
  (let ((n (length buffer)))
    (declare (type (unsigned-byte 16) n))
    (sb-sys:with-pinned-objects (buffer)
      (autowrap:with-alloc (c '(:struct (usbdevfs-ctrltransfer)))
       (setf (usbdevfs-ctrltransfer.b-request-type c) requesttype
         (usbdevfs-ctrltransfer.b-request c) request
         (usbdevfs-ctrltransfer.w-value c) value
         (usbdevfs-ctrltransfer.w-index c) index
         (usbdevfs-ctrltransfer.w-length c) n
         (usbdevfs-ctrltransfer.data c) (sb-sys:vector-sap buffer)
         (usbdevfs-ctrltransfer.timeout c) timeout-ms)

       (assert (= 0  (CFFI-SYS:%FOREIGN-FUNCALL "ioctl"
                        (:INT fd :UNSIGNED-LONG +USBDEVFS-CONTROL+
                              :POINTER (AUTOWRAP:PTR C) :INT)
                        :CONVENTION :CDECL)))))
    buffer))

I would expect that the following line should work instead of my call to cffi-sys:%foreign-funcall:

(ioctl fd +usbdevfs-control+ (autowrap:ptr c)

However this macro-expands as shown below, i.e. the type for the variadic argument c is missing:

(LET ((#:__FD919 FD))
  (LET ((#:__REQUEST920 +USBDEVFS-CONTROL+))
    (CFFI-SYS:%FOREIGN-FUNCALL "ioctl"
                               (:INT #:__FD919 :UNSIGNED-LONG #:__REQUEST920
                                (AUTOWRAP:PTR C) :INT)
                               :CONVENTION :CDECL)))

Here are the software versions, I'm using:

This is SBCL 1.3.5.24-fdc84dc
Linux localhost 4.5.4-1-ARCH #1 SMP PREEMPT Wed May 11 22:21:28 CEST 2016 x86_64
 GNU/Linux
quicklisp/dists/quicklisp/software/cl-autowrap-20160421-git/

Wrapping my head around autoharp

Hi

I know I am missing something...

So: I installed c2ffi and it appears to be working as advertised. Next I am trying to see how c-autowrap works.

Here is my .h file (straight from the README):

// -*- Mode: C++ -*-

/* test.h - abbreviated from example */

typedef struct foo {
  int a, b;
  char c[3];

  struct {
    unsigned int b0 : 2, b1 : 3;

    struct {
      char x, y;
    } s;
  } x[2];
} foo_t;

foo_t* get_foo();
// foo_t* get_foo(int, int);
void free_foo(foo_t *foo);
int* get_int();

Here is my CL file:

;;;; -*- Mode: Lisp -*-

(in-package "CL-AUTOWRAP-TESTS")

(eval-when (:load-toplevel :compile-toplevel :execute)
  (setf autowrap:*c2ffi-program*
        "/Users/marcoxa/Projects/Software/c2ffi/c2ffi/build/bin/c2ffi")
  )

(autowrap:c-include "cl-autowrap-test.h")

If I load this file, I obtain a bunch of .spec files, which contain only [ ]. Nothing else appears to be generated. This is the transcript:

CL-USER 8 > (load "cl-autowrap-test.lisp")
; Loading text file /Users/marcoxa/Projects/Lang/CL/tests/cl-autowrap/cl-autowrap-test.lisp
; Total of 0 compile-time skipped definitions
; Total of 0 compile-time missing entities
; Total of 0 load-time skipped definitions
; Total of 0 load-time missing entities
#P"/Users/marcoxa/Projects/Lang/CL/tests/cl-autowrap/cl-autowrap-test.lisp"

CL-USER 9 > (apropos "GET-FOO")

CL-USER 10 >

I am obviously missing something, but what?

Help please

Thank you

Marco

c-ref to array slot returns first element, not wrapped array

Run the following in order from the repl:

(autowrap:define-foreign-record 'example :struct 128 8
                                '((:a (:array :int 4) :bit-size 128
                                   :bit-offset 0 :bit-alignment 8)))

(autowrap:define-foreign-alias 'example '(:struct (example)))

(autowrap:define-wrapper (:struct (example)))

(defvar *test* (autowrap:alloc 'example))

(plus-c:c-ref *test* example :a)

The result from c-ref is 0 which may well be the first element of the array, but
the expected result is a wrapped array.

c-ref passes build-ref the first field which is :a

:a is a record-field but is not a frf-bitfield so it then calls

(build-ref (car rest) (foreign-type field)
           (autowrap::make-field-ref field current-ref) (cdr rest))

but as (car rest) is nil it calls 'build-ref (null foreign-array)' which doesn't
wrap the result.

Is this expected behavior?

:ANON-TYPE-42 is not the name of a class

Hi

Ok. After many blind alley and discovering the proper clang incantations and loading the library I finally got the test (LWM)

Here is the transcript.

CL-USER 5 > (in-package "CL-AUTOWRAP-TESTS")
#<The CL-AUTOWRAP-TESTS package, 24/64 internal, 38/64 external>

CL-AUTOWRAP-TESTS 6 > (cffi:use-foreign-library cl-autowrap-tests-lib)
#<CFFI:FOREIGN-LIBRARY CL-AUTOWRAP-TESTS-LIB "libcl-autowrap-test.dylib">

CL-AUTOWRAP-TESTS 7 > (get-foo)
#<FOO-T {#X00150F40}>

CL-AUTOWRAP-TESTS 8 > (free-foo *)

CL-AUTOWRAP-TESTS 9 > (let ((foo (get-foo)))
  (setf (foo-t.a foo) 5)             ;; foo.a = 5;
  (setf (foo-t.x[].b0 foo 0) #b10)   ;; foo.x[0].b0 = 2;
  (print (foo-t.x[].s.x foo 1))      ;; anonymous struct
  (foo-t.x[].s foo 0)                ;; => child wrapper
  (foo-t.x[].s& foo 0)               ;; &(foo.x[0].s) => pointer
  (free-foo foo))

0 
Error: #:ANON-TYPE-2247244 is not the name of a class
  1 (continue) Try finding the class #:ANON-TYPE-2247244 again
  2 (abort) Return to level 0.
  3 Return to top loop level 0.

Type :b for backtrace or :c <option number> to proceed.
Type :bug-form "<subject>" for a bug report template or :? for other options.

CL-AUTOWRAP-TESTS 11 : 1 > :b
Call to ERROR
Call to CERROR
Call to FIND-CLASS
Call to CLOS::MAKE-INSTANCE-SYMBOL
Interpreted call to FOO-T.X[].S
Call to LET
Call to EVAL
Call to CAPI::CAPI-TOP-LEVEL-FUNCTION
Call to CAPI::INTERACTIVE-PANE-TOP-LOOP
Call to MP::PROCESS-SG-FUNCTION

Looks like uninterned symbol are not quite palatable as class names in LWM.

Cheers
MA

array of array

If I try to c-include a structure with an array of an array like:

#define MAX_ENUM_STRING_SIZE 26
#define MAX_ENUM_STATES 16
struct test_struct{
    char strs[MAX_ENUM_STATES][MAX_ENUM_STRING_SIZE];
};

autowrap::make-array-accessor ends up in an infinite recursion and the stack gets exhausted eventually.

libffi shared library name

When loading cl-autowrap/libffi, I get an error about not being able to open the shared library "libffi"

Latest libffi by default will build out as libffi-6

If you see CFFI's libffi loading, their form looks like this:

(define-foreign-library (libffi)
  (:darwin (:or "libffi.dylib" "libffi32.dylib" "/usr/lib/libffi.dylib"))
  (:solaris (:or "/usr/lib/amd64/libffi.so" "/usr/lib/libffi.so"))
  (:openbsd "libffi.so")
  (:unix (:or "libffi.so.6" "libffi32.so.6" "libffi.so.5" "libffi32.so.5"))
  (:windows (:or "libffi-6.dll" "libffi-5.dll" "libffi.dll"))
  (t (:default "libffi")))

(see here)

Autowrap's looks like this:

(cffi:define-foreign-library libffi
  (:darwin (:or (:framework "libffi") (:default "libffi")))
  (:unix "libffi.so")
  (:windows "libffi.dll")
  (t (:default "libffi")))

(cffi:use-foreign-library libffi)

I think autowrap should use the same form CFFI does, for completeness

Creating foreign objects

So, c2ffi looks like the best thing since Quicklisp. I used c2ffi-cffi for a YAML parser I'm building, and decided to try cl-autowrap after I heard it made accessors easy.

The only problem is, I can't create anything of any type with CFFI:WITH-FOREIGN-OBJECT, and libyaml has no equivalent of the GET-FOO function in the example. Does the SFFI abstraction layer have anything that works like it? I found some unexported functions, MAKE-[type name], but they all seem to return null pointers.

An alternative would be to create my own C file with functions, but then this is exactly what I was doing before with c2ffi-cffi to make accessors simpler and I'd prefer to eliminate a dependency on a C compiler for a simple parser.

Error when using c function that return type bool

C function prototype

bool wlc_init(const struct wlc_interface *interface, int argc, char *argv[]);

My lisp code

(defun init (i argc argv)
  (wlc-ffi.functions:wlc-init i argc argv))

The error

; caught ERROR:
;   during macroexpansion of
;   (CFFI-SYS:%FOREIGN-FUNCALL "wlc_init" (:POINTER WLC-FFI::INTERFACE :INT ...)
;                              ...).
;   Use *BREAK-ON-SIGNALS* to intercept.
;   
;    :-BOOL fell through ECASE expression.
;    Wanted one of (:CHAR :UNSIGNED-CHAR :SHORT :UNSIGNED-SHORT :INT :UNSIGNED-INT
;                   :LONG :UNSIGNED-LONG :LONG-LONG :UNSIGNED-LONG-LONG :FLOAT
;                   :DOUBLE :POINTER :VOID).

Not sure if I'm doing something just wrong here but I have no idea how to add the type _Bool into cffi.
Here's the c-include if it matters, I also tried with with including "stdbool.h" but that had no effect on the error.

(autowrap:c-include "wlc/wlc.h"
 :accessor-package :wlc-ffi.accessors
 :function-package :wlc-ffi.functions
 :spec-path "/ss/prog/lisp/aw-wlc/"
 :exclude-sources ("/usr/local/lib/clang/([^/]*)/include/(?!stddef.h)"
           "/usr/include/")
 :include-sources ("stdint.h"
           "sys/types.h"
           "/usr/local/include/"))

Class is not yet defined or was undefined; T names a defined constant.

Pulled c2ffi at Feb 18 05:24 (SHA1 value: 9a69c865193e6182cd9fce59cf1772ef883526a7), installed cl-autowrap-20160208-git with quicklisp, using SBCL 1.3.1 and trying to wrap libdrm. Seems like no problem with JSON generation. But. Here is code I run:

(asdf:oos 'asdf:load-op :cffi)
(asdf:oos 'asdf:load-op :cl-autowrap)
(defpackage :libdrm-ffi
  (:use #:common-lisp
    #:cffi)
  (:documentation ""))

(in-package #:libdrm-ffi)
(define-foreign-library libdrm
    (t (:default "libdrm"))) ; /usr/lib/x86_64-linux-gnu/libdrm.so
(use-foreign-library libdrm)
(setf autowrap:*c2ffi-program* #P"/home/y/stand/c2ffi/build/src/c2ffi")
(autowrap:c-include #P"/usr/include/xf86drm.h"
            :sysincludes '("/usr/include/x86_64-linux-gnu/"
                   "/usr/include/libdrm/")
            :spec-path #P"/home/y/dev/drm/autowrap/spec/")

Here is resulting codition:

Execution of a form compiled with errors.
Form:
  (DEFSTRUCT
    (DRM-STATS-T (:CONSTRUCTOR MAKE-DRM-STATS-T) (:CONC-NAME "DRM-STATS-T-")
     (:INCLUDE _DRM_STATS)))
Compile-time error:
  (during macroexpansion of (DEFSTRUCT (DRM-STATS-T # ...)))
Class is not yet defined or was undefined: _DRM_STATS
   [Condition of type SB-INT:COMPILED-PROGRAM-ERROR]

There is no _drm_stats objects of any kind neither in JSON, nor in C sources. Only drm_stats (without prefixed underscore).

And when I evaluate the same autowrap:c-include form again without any changes applied to any code, I suddenly got a lot of errors like this:

  error: 
    T names a defined constant, and cannot be used as a local variable.
    --> PROGN EVAL-WHEN AUTOWRAP:DEFINE-CFUN DEFMACRO PROGN EVAL-WHEN 
    --> SB-C::%DEFMACRO SB-C::%DEFMACRO SB-INT:NAMED-LAMBDA FUNCTION 
    --> SB-C::NAMED-DS-BIND SB-INT:BINDING* 
    ==>
      (LET* ((#:G32226 (SB-C::CHECK-DS-LIST (CDR #:EXPR) 1 1 '(# T)))
             (T (POP #:G32226)))
        (BLOCK LIBDRM-FFI:DRM-HASH-DESTROY
          (LET ((#:!FUN32223 #))
            (WITH-SLOTS (#)
                #:!FUN32223
              (AUTOWRAP::FOREIGN-TO-FFI # '# # #:!FIELDS32224 #)))))

Accessing an element at an index from an array of structs through c-ref

From the c-plus examples:

(c-ref object foo-t :a)              ;; => object.a
(c-ref object foo-t :c 2)            ;; => object.c[2]
(c-ref object foo-t :x 2 :b0)        ;; => object.x[2].b0
(c-ref object foo-t :x :b0)          ;; => object.x[0].b0
(c-ref object foo-t :c *)            ;; => *(object.c)
(c-ref object foo-t :x 1 :s :x &)    ;; => &(object.x[1].s.x)

Is there a simpler way to access an element at an index from an array of structs?

(...)              ;; => object[1].a

Currently, I get a pointer first using c-aptr:

(c-with ((iovec (:struct (c:iovec)) :count 2))
      (c-ref (c-aptr iovec 0 '(:struct (c:iovec))) ;; pointer to struct at index 0
             (:struct (c:iovec)) ;; pointer type
             :iov-len)) ;; member

A cleaner way would be something like:

(c-with ((iovec (:struct (c:iovec)) :count 2))
      (iovec :index 0 :iov-len))

c-including /usr/include/lzma/LzmaEnc.h fails

(autowrap:c-include "/usr/include/lzma/LzmaEnc.h") fails with error code 134 for me.

This is from freshly compiled branch clang-4.0.0.

https://pastebin.com/0TmJKZxz <- logs from running the c2ffi command manually. Last line:

c2ffi: /usr/lib/llvm-4.0/include/clang/AST/Expr.h:1532: llvm::StringRef clang::StringLiteral::getString() const: Assertion `CharByteWidth==1 && "This function is used in places that assume strings use char"' failed.

Swank autodoc problems

I could've sworn it worked before! I am not getting any Emacs autodoc function parameter help with an autowrapped library. Watching slime-events shows that autodoc responds with 'not available'. Is there a trick to get it working, or is it just not supported?
Note that symbol completions work fine.

autowrap:define-bitmask fails under a 32-bit lisp

Something is amiss when using autowrap:define-bitmask in a 32-bit environment. Somehow (<-2 nil nil) is getting evaluated instead of what would normally be expected.

Tried under sbcl 1.0.58 and Clozure 1.9.

Autowrap of nfs/termbox fails to include structs

While autowrapping termbox (https://github.com/nsf/termbox), I can't get any structs to be wrapped, resulting in a compile-time error and the following note from SBCL:

Note: skipping determine the basic type of foreign type TB-EVENT due to
undefined foreign type: TB-EVENT

All that is in my primary Lisp file is the following:

(asdf:load-system :cl-plus-c)
(use-package :plus-c)
(cffi-sys:%load-foreign-library
 :libtest #p"/home/username/termbox-directory/usr/local/lib/libtermbox.so")
(autowrap:c-include "/home/username/termbox-directory/usr/local/include/termbox.h")
(plus-c:c-let ((event tb-event :free t))
       (print event))

I'm probably doing something wrong, but for the life of me I can't determine what.

Erroneous incomplete type "struct uiInitOptions" when wrapping libui

This doesn't reproduce with a minimal testcase of:

typedef struct foo foo;

struct foo {
    int x;
};

But does happen with the header here: https://github.com/andlabs/libui/blob/80b8fddbea397a7970532b5ac44c552d90cb3c81/ui.h

The .spec file generated seems to think uiInitOptions an incomplete type: https://gist.github.com/anonymous/bb9764df433cc262635c24cb7fedd663 I don't know if this is a c2ffi issue or a cl-autowrap issue as I haven't delved into the details of the implementation.

CL-AUTOWRAP vs. Clutter: some breakage

Good day!

I'm trying to make cl-autowrap generate bindings for libclutter & family.

I've created a cl-autowrap.lisp file, as per the CL-AUTOWRAP documentation,
as can be seen in the following repository:

https://github.com/deepfire/cffi-clutter/tree/cl-autowrap

..and then I do:

sbcl --eval '(require :cl-autowrap)' --eval '(load (compile-file "cl-autowrap.lisp"))'

The binding generation fails in many ways, as is reflected in the attached file.

Autowrap/CFFI: the split world

Sometimes the impedance mismatch between CFFI and Autowrap abstractions comes to bite.

As an example, the following does not work, so it appears as if one has to resort to CFFI:WITH-FOREIGN-OBJECTS:

(c-dxlet ((argc :int)
                (argv (:pointer (:string))))
        (setf argc 0
              argv 0)
        (clutter-init (argc &) (argv &)))

Another instance is checking for the NULL pointer -- CFFI:NULL-POINTER-P does not work, as one has to unwrap the objects with AUTOWRAP:PTR.

Latest commit breaks ZMQ4L

I'm going to take a look into this myself, but I just wanted to share: The latest commit (with hash cd30484) breaks ZMQ4L with the following error:

[package zmq4]..> Error: :UNSIGNED-INT can't be destructured against the lambda list (AUTOWRAP::ANON-RECORD-TYPE AUTOWRAP::ANON-PARAMS COMMON-LISP:&REST AUTOWRAP::ANON-FIELD-LIST), because it does not contain at least 2 elements.
> While executing: CCL::PREPARE-TO-DESTRUCTURE, in process listener(1).

I'm going to take a look into fixing this, but you as the creator & maintainer of the package might know exactly what is broken by looking at it!

DEFINE-FOREIGN-TYPE callers followed by DEFINE-ACCESSOR leads to failure

Good day Ryan!

It appears that there is a load/compile time issue wrt. ordering
of funcalled type definers vs. the macroexpansion of DEFINE-ACCESSORS.
For example, in expasion of C-INCLUDE:

    (AUTOWRAP::DEFINE-FOREIGN-RECORD 'SIGACTION :STRUCT 1216 64
                                     '((__SIGACTION_HANDLER
                                        (UNION
                                         (NIL :ID 27 :BIT-SIZE 64
                                          :BIT-ALIGNMENT 64)
                                         (SA-HANDLER __SIGHANDLER_T :BIT-SIZE
                                          64 :BIT-OFFSET 0 :BIT-ALIGNMENT 64)
                                         (SA-SIGACTION (:POINTER (:VOID))
                                          :BIT-SIZE 64 :BIT-OFFSET 0
                                          :BIT-ALIGNMENT 64))
                                        :BIT-SIZE 64 :BIT-OFFSET 0
                                        :BIT-ALIGNMENT 64)
                                       (SA-MASK __SIGSET_T :BIT-SIZE 1024
                                        :BIT-OFFSET 64 :BIT-ALIGNMENT 64)
                                       (SA-FLAGS :INT :BIT-SIZE 32 :BIT-OFFSET
                                        1088 :BIT-ALIGNMENT 32)
                                       (SA-RESTORER (:POINTER (:VOID))
                                        :BIT-SIZE 64 :BIT-OFFSET 1152
                                        :BIT-ALIGNMENT 64)))
 ...
 (AUTOWRAP:DEFINE-ACCESSORS (:STRUCT (SIGACTION))
                            #<PACKAGE "COMMON-LISP-USER">)

Nicer string literal passing needed

Whenever I have to pass a string literal to a function, I have to do things like this:

(with-foreign-strings ((text "Press <space> to reset the image position."))
  (clutter-text-new-with-text (make-pointer 0) text))

It'd be nicer if the call would detect them strings, and produce the W-F-S automatically..

c-ref expansion contains literal CLOS objects

form:

(c-ref hci-filter hci-filter :event-mask)

expansion:

(LET ((#:WRAPPER1448 HCI-FILTER))
  (CFFI-SYS:%MEM-REF (CFFI-SYS:INC-POINTER (PTR #:WRAPPER1448) 4) #<AUTOWRAP:FOREIGN-ALIAS UINT32-T {10075361E3}>)

hci-filter FFI def:

(AUTOWRAP:DEFINE-FOREIGN-RECORD 'HCI-FILTER :STRUCT 128 32
                                    '((:TYPE-MASK UINT32-T :BIT-SIZE 32 :BIT-OFFSET 0 :BIT-ALIGNMENT 32)
                                      (:EVENT-MASK (:ARRAY UINT32-T 2) :BIT-SIZE 64 :BIT-OFFSET 32 :BIT-ALIGNMENT 32)
                                      (:OPCODE UINT16-T :BIT-SIZE 16 :BIT-OFFSET 96 :BIT-ALIGNMENT 16)))

trace:

  0: (PLUS-C::BUILD-REF :EVENT-MASK #<AUTOWRAP:FOREIGN-ALIAS HCI-FILTER {100753CA03}> (PTR #:WRAPPER1448) NIL)
    1: (PLUS-C::BUILD-REF :EVENT-MASK #<AUTOWRAP:FOREIGN-RECORD HCI-FILTER {1007ACFF83}> (PTR #:WRAPPER1448) NIL)
      2: (PLUS-C::BUILD-REF NIL #<AUTOWRAP:FOREIGN-ARRAY TO-TYPE:UINT32-T {1008E8B663}> (CFFI-SYS:INC-POINTER (PTR #:WRAPPER1448) 4) NIL)
      2: PLUS-C::BUILD-REF returned (CFFI-SYS:%MEM-REF (CFFI-SYS:INC-POINTER (PTR #:WRAPPER1448) 4) #<AUTOWRAP:FOREIGN-ALIAS UINT32-T {10075361E3}>)
    1: PLUS-C::BUILD-REF returned (CFFI-SYS:%MEM-REF (CFFI-SYS:INC-POINTER (PTR #:WRAPPER1448) 4) #<AUTOWRAP:FOREIGN-ALIAS UINT32-T {10075361E3}>)
  0: PLUS-C::BUILD-REF returned (CFFI-SYS:%MEM-REF (CFFI-SYS:INC-POINTER (PTR #:WRAPPER1448) 4) #<AUTOWRAP:FOREIGN-ALIAS UINT32-T {10075361E3}>)

The name of `C-LET` is confusing

I find that the default of c-let is confusing, semantically.

Having agonised over the choice of better names for the :free T/NIL and :ptr variants, I've finally come to this:

  1. The real LET -- equivalent to WITH-FOREIGN-OBJECTS -- C-LET
  2. The 'no release' (:free nil) variant -- C-LET-RETAIN
  3. The pointer variant -- C-LET-PTR.

What do you think?

The current need to specify the :options feels like a kludge..

Obscurity of a successful library wrapping

What do you get, when CL-AUTOWRAP succeeds?

Currently it is a Lisp image with the C library loaded and the
corresponding Lisp artifacts defined.

The problem with this is that this is rather obscure.

It would be nicer to have some text generated, as this will facilitate:

  1. visual enumerability
  2. jump-to-source

Passing and returning structs by value

I'm trying to autowrap Chipmunk2D, a C library for 2D physics simulation: https://github.com/slembcke/Chipmunk2D

Many functions return and receive by value a structure that represents a 2D vector (cpVect if you are interested).

In the FAQs you mention to let you know if passing structs by value is necessary so you can prioritize this issue :D

What do you think? Is it doable?

Thank you!

Symbol conflicts with CFFI

The following is what is required to use both CFFI and AUTOWRAP packages:

  (:shadowing-import-from :autowrap
                          #:foreign-type-size #:foreign-pointer
                          #:defcallback #:callback
                          #:define-foreign-type)

Parameters named t do not work

Consider /tmp/foo.h containing:

int x(void *t);
CL-USER> (autowrap:c-include "/tmp/foo.h")
; in: AUTOWRAP:C-INCLUDE "/tmp/foo.h"
;     (SB-INT:NAMED-DS-BIND (:MACRO X . DEFMACRO)
;         (T)
;         (CDR #:EXPR)
;       (BLOCK X
;         (LET ((#:!FUN1850 #))
;           (WITH-SLOTS (#)
;               #:!FUN1850
;             (AUTOWRAP::FOREIGN-TO-FFI # '# # #:!FIELDS1851 #)))))
; --> SB-INT:BINDING*
; ==>
;   (LET* ((#:G0 (SB-C::CHECK-DS-LIST (CDR #:EXPR) 1 1 '(# T))) (T (POP #:G0)))
;     (BLOCK X
;       (LET ((#:!FUN1850 #))
;         (WITH-SLOTS (#)
;             #:!FUN1850
;           (AUTOWRAP::FOREIGN-TO-FFI # '# # #:!FIELDS1851 #)))))
;
; caught ERROR:
;   T names a defined constant, and cannot be used as a local variable.

;     (SB-INT:NAMED-LAMBDA (MACRO-FUNCTION X)
;         (#:EXPR #:ENV)
;       (DECLARE (SB-C::LAMBDA-LIST (T)))
;       (DECLARE (IGNORE #:ENV))
;       (SB-INT:NAMED-DS-BIND (:MACRO X . DEFMACRO)
;           (T)
;           (CDR #:EXPR)
;         (BLOCK X
;           (LET (#)
;             (WITH-SLOTS #
;                 #:!FUN1850
;               #)))))
;
; caught STYLE-WARNING:
;   The variable #:EXPR is defined but never used.
;
; compilation unit finished
;   caught 1 ERROR condition
;   caught 1 STYLE-WARNING condition
; Total of 0 compile-time skipped definitions
; Total of 0 compile-time missing entities
; Total of 0 load-time skipped definitions
; Total of 0 load-time missing entities

Unable to exclude a symbol from an included source.

My project is autowrapped-ode and my use case is as follows:

  • ODE comes in double or single float precision flavours
  • ODE defines its base floating point type as dReal which is float or double depending on the above
  • ODE defines all of its other types in terms of dReal
  • I can detect the precision using this code
  • The above means I can define dReal correctly using this code

However c-include then redefines dReal and I can see a way to exclude it. The reason is that #'read-parse-forms has the following condition.

(and (or (included-p name exclude-definitions)
         (included-p location exclude-sources))
     (not (or (included-p name include-definitions)
              (included-p location include-sources))))

Which means that if I included the source I cant exclude a symbol.

One possibility is we could allow :include-sources to be used like this:

:include-sources ("odeinit.h"
                  ("common.h" :except "dReal"))

If this is something you would like but do not have time to implement I think I can add this. Please let me know.

Thanks again for this incredible project

Problem with anonymous union

I use c-include on the following structure with an unnamed union. Every call of c-include produces a
different accessor name in Common Lisp, e.g. (usbdevfs-urb.field-803.stream-id u) or (usbdevfs-urb.field-1187.stream-id u). This is quite inconvenient, because I have to change the Lisp code, in particular when I copy the spec file to a computer without c2ffi.

struct usbdevfs_urb {
        unsigned char type;
        unsigned char endpoint;
        int status;
        unsigned int flags;
        void *buffer;
        int buffer_length;
        int actual_length;
        int start_frame;
        union {
                int number_of_packets;  /* Only used for isoc urbs */
                unsigned int stream_id; /* Only used with bulk streams */
        };
        int error_count;
        unsigned int signr;     /* signal to be sent on completion,
                                  or 0 if none should be sent. */
        void *usercontext;
        struct usbdevfs_iso_packet_desc iso_frame_desc[0];
};
(AUTOWRAP:DEFINE-FOREIGN-RECORD 'USBDEVFS-URB :STRUCT 448 64
                                    '((:TYPE :UNSIGNED-CHAR :BIT-SIZE 8
                                       :BIT-OFFSET 0 :BIT-ALIGNMENT 8)
                                      (:ENDPOINT :UNSIGNED-CHAR :BIT-SIZE 8
                                       :BIT-OFFSET 8 :BIT-ALIGNMENT 8)
                                      (:STATUS :INT :BIT-SIZE 32 :BIT-OFFSET 32
                                       :BIT-ALIGNMENT 32)
                                      (:FLAGS :UNSIGNED-INT :BIT-SIZE 32
                                       :BIT-OFFSET 64 :BIT-ALIGNMENT 32)
                                      (:BUFFER (:POINTER :VOID) :BIT-SIZE 64
                                       :BIT-OFFSET 128 :BIT-ALIGNMENT 64)
                                      (:BUFFER-LENGTH :INT :BIT-SIZE 32
                                       :BIT-OFFSET 192 :BIT-ALIGNMENT 32)
                                      (:ACTUAL-LENGTH :INT :BIT-SIZE 32
                                       :BIT-OFFSET 224 :BIT-ALIGNMENT 32)
                                      (:START-FRAME :INT :BIT-SIZE 32
                                       :BIT-OFFSET 256 :BIT-ALIGNMENT 32)
                                      (#:FIELD-1187
                                       (UNION
                                        (NIL :ID 22 :BIT-SIZE 32 :BIT-ALIGNMENT
                                         32)
                                        (:NUMBER-OF-PACKETS :INT :BIT-SIZE 32
                                         :BIT-OFFSET 0 :BIT-ALIGNMENT 32)
                                        (:STREAM-ID :UNSIGNED-INT :BIT-SIZE 32
                                         :BIT-OFFSET 0 :BIT-ALIGNMENT 32))
                                       :BIT-SIZE 32 :BIT-OFFSET 288
                                       :BIT-ALIGNMENT 32)
                                      (:ERROR-COUNT :INT :BIT-SIZE 32
                                       :BIT-OFFSET 320 :BIT-ALIGNMENT 32)
                                      (:SIGNR :UNSIGNED-INT :BIT-SIZE 32
                                       :BIT-OFFSET 352 :BIT-ALIGNMENT 32)
                                      (:USERCONTEXT (:POINTER :VOID) :BIT-SIZE
                                       64 :BIT-OFFSET 384 :BIT-ALIGNMENT 64)
                                      (:ISO-FRAME-DESC
                                       (:ARRAY
                                        (:STRUCT (USBDEVFS-ISO-PACKET-DESC)) 0)
                                       :BIT-SIZE 0 :BIT-OFFSET 448
                                       :BIT-ALIGNMENT 32)))

FOREIGN-TYPE-SIZE seems not wrapped

Hey,

(autowrap:c-include "/usr/include/lzma/LzmaDec.h") ;; this works
(foreign-type-size '(:struct c-lzma-enc-props))

This complains: Unknown CFFI type (:STRUCT C-LZMA-ENC-PROPS)

The structure is wrapped correctly and the accessor works, but it looks like the defctype or defcstruct was not called. Because, if it was called, then FOREIGN-TYPE-SIZE would not complain, correct?

need something like :include-sources

Often it seems easier to specify a pattern for the sources
to include rather then to exclude. So, either we need
a :include-sources or a way to invert the pattern match for
patterns in :exclude-sources - maybe:

:exclude-sources ("foo.h"
("my_target" :invert))

TIA Ralf Mattes

:exclude-sources does not really seem to work sometimes

While attempting to bind clutter, like this:

(autowrap:c-include "clutter-raw.h"
                      :exclude-arch ("i686-pc-linux-gnu"
                                     "i686-pc-win32"
                                     "x86_64-pc-win64"
                                     "i686-apple-darwin9"
                                     "x86_64-apple-darwin9")
                      :exclude-sources ("/usr/include/clutter-1.0/clutter/clutter-keysyms.h")
                      :sysincludes '("/usr/include/clutter-1.0/clutter"
                                     "/usr/include/clutter-1.0"
                                     "/usr/include/cogl"
                                     "/usr/include/pango-1.0"
                                     "/usr/include/atk-1.0"
                                     "/usr/include/glib-2.0"
                                     "/usr/include/json-glib-1.0"
                                     "/usr/lib64/glib-2.0/include"
                                     "/usr/include/cairo"
                                     "/usr/include/freetype2"
                                     "/usr/include/libpng15"
                                     "/usr/include/pixman-1"))

..where clutter-raw.h is:

#include <clutter/clutter.h>
#include <cogl/cogl.h>
#include <GL/gl.h>

..the :exclude-sources directive does not seem to have effect,
as the misconstrued constant definitions still seem to seep through
(and deliver the damage.. but it's another issue..)

Include a way to specify language to c2ffi

I'm writing a wrapper to OpenCV (as all the others are out of date & don't work on windows) and nothing was working properly. I'm simply trying to load up an image with OpenCV's imread function, and that function was missing. running c2ffi on a simple test file that included all the sources gave me a spec file that had everything in it, but when generating with cl-autowrap, it never did.

Finally I tried getting the output, and looking at the temp files it generates, and that is where i found my problem! First, you generate a tmpBLAH.tmp file that has a bunch of c2ffi defs & such, then you generate a tmpBLAH2.tmp that #includes the given file, along with the previous tmpBLAH.tmp file. now when c2ffi runs this, it seems to assume it's plain C, and so if my header is a C++ header instead of a C one (as is the case for OpenCV stuff) you get the following:

In file included from /tmp/tmp6F83SDCV.tmp:1:
In file included from /media/sf_local-projects/opencv-lisp/src/spec/opencv.hpp:46:
/usr/include/opencv2/core.hpp:49:4: error: core.hpp header must be compiled as C++
#  error core.hpp header must be compiled as C++
   ^

etc...

The solution is very simple, take the aforementioned tmpBLAH2.tmp files, rename them to tempBLAH2.hpp and run those through c2ffi by hand w/ the proper arguments! Though it would be nice if the "run those through c2ffi by hand" part would disappear. Maybe it's as simple as changing it so the *.tmp files are named *.<extension-of-the-given-file> instead?

Name conversion heuristics: behaves like one : -)

The following names are what I get when wrapping Glib:

;   G-BOOKMARK-FILE-SET-VISITED G-CCLOSURE-MARSHAL-BOOLEAN--BOXED-BOXE-DV
;   G-CCLOSURE-MARSHAL-BOOLEAN--FLAG-SV
;   G-CCLOSURE-MARSHAL-STRING--OBJECT-POINTE-RV
;   G-CCLOSURE-MARSHAL-VOID--BOOLEA-NV G-CCLOSURE-MARSHAL-VOID--BOXE-DV
;   G-CCLOSURE-MARSHAL-VOID--CHA-RV G-CCLOSURE-MARSHAL-VOID--DOUBL-EV
;   G-CCLOSURE-MARSHAL-VOID--ENU-MV G-CCLOSURE-MARSHAL-VOID--FLAG-SV
;   G-CCLOSURE-MARSHAL-VOID--FLOA-TV G-CCLOSURE-MARSHAL-VOID--IN-TV
;   G-CCLOSURE-MARSHAL-VOID--LON-GV G-CCLOSURE-MARSHAL-VOID--OBJEC-TV
;   G-CCLOSURE-MARSHAL-VOID--PARA-MV G-CCLOSURE-MARSHAL-VOID--POINTE-RV
;   G-CCLOSURE-MARSHAL-VOID--STRIN-GV G-CCLOSURE-MARSHAL-VOID--UCHA-RV
;   G-CCLOSURE-MARSHAL-VOID--UIN-TV G-CCLOSURE-MARSHAL-VOID--UINT-POINTE-RV
;   G-CCLOSURE-MARSHAL-VOID--ULON-GV G-CCLOSURE-MARSHAL-VOID--VARIAN-TV
;   G-CCLOSURE-MARSHAL-VOID--VOI-DV

call-by-value not yet implemented...

I wrapped a C library, and trying to call a function results in
; Evaluation aborted on #<SIMPLE-ERROR "Call-by-value not implemented yet for ~S" {...}>.

Any suggestions?

P.S. Even simple calls to functions that take no arguments result in this, so I have trouble believing that it is somehow related to struct-by-value problems in an earlier issue...

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.