FFI reference mostly Scribbled

svn: r7942
This commit is contained in:
Matthew Flatt 2007-12-10 22:39:38 +00:00
parent 9230f66f01
commit 102249efc4
13 changed files with 1745 additions and 45 deletions

View File

@ -227,7 +227,7 @@
verbatim)
(provide image onscreen menuitem defterm
schemefont schemevalfont schemeresultfont schemeidfont
schemefont schemevalfont schemeresultfont schemeidfont schemevarfont
schemeparenfont schemekeywordfont schememetafont schememodfont
filepath exec envvar Flag DFlag
indexed-file indexed-envvar
@ -259,6 +259,8 @@
(make-element "schemeresult" (decode-content str)))
(define (schemeidfont . str)
(make-element "schemesymbol" (decode-content str)))
(define (schemevarfont . str)
(make-element "schemevariable" (decode-content str)))
(define (schemeparenfont . str)
(make-element "schemeparen" (decode-content str)))
(define (schememetafont . str)
@ -436,7 +438,7 @@
;; ----------------------------------------
(provide declare-exporting
defproc defproc* defstruct defthing defparam defboolparam
defproc defproc* defstruct defthing defthing* defparam defboolparam
defform defform* defform/subs defform*/subs defform/none
defidform
specform specform/subs
@ -671,7 +673,13 @@
(define-syntax defthing
(syntax-rules ()
[(_ id result desc ...)
(*defthing (quote-syntax/loc id) 'id #f (schemeblock0 result) (lambda () (list desc ...)))]))
(*defthing (list (quote-syntax/loc id)) (list 'id) #f (list (schemeblock0 result))
(lambda () (list desc ...)))]))
(define-syntax defthing*
(syntax-rules ()
[(_ ([id result] ...) desc ...)
(*defthing (list (quote-syntax/loc id) ...) (list 'id ...) #f (list (schemeblock0 result) ...)
(lambda () (list desc ...)))]))
(define-syntax defparam
(syntax-rules ()
[(_ id arg contract desc ...)
@ -1285,42 +1293,43 @@
fields field-contracts)))
(content-thunk))))
(define (*defthing stx-id name form? result-contract content-thunk)
(define (*defthing stx-ids names form? result-contracts content-thunk)
(define spacer (hspace 1))
(make-splice
(cons
(make-table
'boxed
(list
(list
(make-flow
(make-table-if-necessary
"argcontract"
(list
(list (make-flow
(list
(make-paragraph
(list (let ([tag ((if form? id-to-form-tag id-to-tag) stx-id)]
[content (list (definition-site name stx-id form?))])
(if tag
(make-toc-target-element
#f
(list (make-index-element #f
content
tag
(list (symbol->string name))
content
(with-exporting-libraries
(lambda (libs)
(make-thing-index-desc name libs)))))
tag)
(car content)))
spacer ":" spacer))))
(make-flow
(list
(if (flow-element? result-contract)
result-contract
(make-paragraph (list result-contract))))))))))))
(map (lambda (stx-id name result-contract)
(list
(make-flow
(make-table-if-necessary
"argcontract"
(list
(list (make-flow
(list
(make-paragraph
(list (let ([tag ((if form? id-to-form-tag id-to-tag) stx-id)]
[content (list (definition-site name stx-id form?))])
(if tag
(make-toc-target-element
#f
(list (make-index-element #f
content
tag
(list (symbol->string name))
content
(with-exporting-libraries
(lambda (libs)
(make-thing-index-desc name libs)))))
tag)
(car content)))
spacer ":" spacer))))
(make-flow
(list
(if (flow-element? result-contract)
result-contract
(make-paragraph (list result-contract)))))))))))
stx-ids names result-contracts))
(content-thunk))))
(define (meta-symbol? s) (memq s '(... ...+ ?)))
@ -2055,7 +2064,10 @@
(make-sig-desc l))
(define (*defsignature stx-id supers body-thunk indent?)
(*defthing stx-id (syntax-e stx-id) #t (make-element #f '("signature"))
(*defthing (list stx-id)
(list (syntax-e stx-id))
#t
(list (make-element #f '("signature")))
(lambda ()
(let ([in (parameterize ([current-signature (make-sig
(id-to-form-tag stx-id))])

View File

@ -60,16 +60,18 @@
i)))
(define (typeset-atom c out color? quote-depth)
(let-values ([(s it? sub?)
(let ([c (syntax-e c)])
(let ([s (format "~s" c)])
(if (and (symbol? c)
((string-length s) . > . 1)
(char=? (string-ref s 0) #\_))
(values (substring s 1) #t #f)
(values s #f #f))))]
[(is-var?) (and (identifier? c)
(memq (syntax-e c) (current-variable-list)))])
(let*-values ([(is-var?) (and (identifier? c)
(memq (syntax-e c) (current-variable-list)))]
[(s it? sub?)
(let ([sc (syntax-e c)])
(let ([s (format "~s" sc)])
(if (and (symbol? sc)
((string-length s) . > . 1)
(char=? (string-ref s 0) #\_)
(not (or (identifier-label-binding c)
is-var?)))
(values (substring s 1) #t #f)
(values s #f #f))))])
(if (or (element? (syntax-e c))
(delayed-element? (syntax-e c)))
(out (syntax-e c) #f)

View File

@ -0,0 +1,255 @@
#lang scribble/doc
@(require "utils.ss")
@title{Derived Utilities}
@section[#:tag "foreign:tagged-pointers"]{Tagged C Pointer Types}
@defproc*[([(cpointer-has-tag? [cptr any/c][tag any/c]) boolean?]
[(cpointer-push-tag! [cptr any/c][tag any/c]) void])]{
These two functions treat pointer tags as lists of tags. As described
in @secref["foreign:pointer-funcs"], a pointer tag does not have any
role, except for Scheme code that uses it to distinguish pointers;
these functions treat the tag value as a list of tags, which makes it
possible to construct pointer types that can be treated as other
pointer types, mainly for implementing inheritance via upcasts (when a
struct contains a super struct as its first element).
The @scheme[cpointer-hash-tag] function checks whether if the given
@scheme[cptr] has the @scheme[tag]. A pointer has a tag @scheme[tag]
when its tag is either @scheme[eq?] to @scheme[tag] or a list that
contains (@scheme[memq]) @scheme[t].
The @scheme[cpointer-push-tag!] function pushes the given @scheme[tag]
value on @scheme[cptr]'s tags. The main properties of this operation
are: (a) pushing any tag will make later calls to
@scheme[cpointer-has-tag?] succeed with this tag, and (b) the pushed tag
will be used when printing the pointer (until a new value is pushed).
Technically, pushing a tag will simply set it if there is no tag set,
otherwise push it on an existing list or an existing value (treated as
a single-element list).}
@defproc*[([(_cpointer [tag any/c]
[ptr-type ctype? _pointer]
[scheme-to-c (any/c . -> . any/c) values]
[c-to-scheme (any/c . -> . any/c) values])
ctype]
[(_cpointer/null [tag any/c]
[ptr-type ctype? _pointer]
[scheme-to-c (any/c . -> . any/c) values]
[c-to-scheme (any/c . -> . any/c) values])
ctype])]{
Construct a kind of a pointer that gets a specific tag when converted
to Scheme, and accept only such tagged pointers when going to C. An
optional @scheme[ptr-type] can be given to be used as the base pointer
type, instead of @scheme[_pointer].
Pointer tags are checked with @scheme[cpointer-has-tag?] and changed
with @scheme[cpointer-push-tag!] which means that other tags are
preserved. Specifically, if a base @scheme[ptr-type] is given and is
itself a @scheme[_cpointer], then the new type will handle pointers
that have the new tag in addition to @scheme[ptr-type]'s tag(s). When
the tag is a pair, its first value is used for printing, so the most
recently pushed tag which corresponds to the inheriting type will be
displayed.
Note that tags are compared with @scheme[eq?] (or @scheme[memq]), which means
an interface can hide its value from users (e.g., not provide the
@scheme[cpointer-tag] accessor), which makes such pointers un-fake-able.
@scheme[_cpointer/null] is similar to @scheme[_cpointer] except that
it tolerates @cpp{NULL} pointers both going to C and back. Note that
@cpp{NULL} pointers are represented as @scheme[#f] in Scheme, so they
are not tagged.}
@defform*[[(define-cpointer-type _id)
(define-cpointer-type _id scheme-to-c-expr)
(define-cpointer-type _id scheme-to-c-expr c-to-scheme-expr)]]{
A macro version of @scheme[_cpointer] and @scheme[_cpointer/null],
using the defined name for a tag string, and defining a predicate
too. The @scheme[_id] must start with @litchar{_}.
The optional expression produces optional arguments to @scheme[_cpointer].
In addition to defining @scheme[_id] to a type generated by
@scheme[_cpointer], @scheme[_foo]@schemeidfont{/null} is bound to a
type produced by @scheme[_cpointer/null] type. Finally,
@schemevarfont{id}@schemeidfont{?} is defined as a predicate, and
@schemevarfont{id}@schemeidfont{-tag} is defined as an accessor to
obtain a tag. The tag is the string form of @schemevarfont{id}.}
@; ------------------------------------------------------------
@section[#:tag "foreign:cvector"]{Safe C Vectors}
The @scheme[cvector] form can be used as a type C vectors (i.e., a the
pointer to the memory block)
@defproc[(make-cvector [type ctype?][length exact-nonnegative-integer?]) cvector?]{
Allocates a C vector using the given @scheme[type] and
@scheme[length].}
@defproc[(cvector [type ctype?][val any/c] ...) cvector?]{
Creates a C vector of the given @scheme[type], initialized to the
given list of @scheme[val]s.}
@defproc[(cvector? [v any/c]) boolean?]{
Returns @scheme[#t] if @scheme[v] is a C vector, @scheme[#f] otherwise.}
@defproc[(cvector-length [cvec cvector?]) exact-nonnegative-integer?]{
Returns the length of a C vector.}
@defproc[(cvector-type [cvec cvector?]) ctype?]{
Returns the C type object of a C vector.}
@defproc[(cvector-ref [cvec cvector?][k exact-nonnegative-integer?]) any]{
References the @scheme[k]th element of the @scheme[cvec] C vector.
The result has the type that the C vector uses.}
@defproc[(cvector-set! [cvec cvector?][k exact-nonnegative-integer?][val any]) void?]{
Sets the @scheme[k]th element of the @scheme[cvec] C vector to
@scheme[val]. The @scheme[val] argument should be a value that can be
used with the type that the C vector uses.}
@defproc[(cvector->list [cvec cvector?]) list?]{
Converts the @scheme[cvec] C vector object to a list of values.}
@defproc[(list->cvector [lst list?][type ctype?]) cvector?]{
Converts the list @scheme[lst] to a C vector of the given
@scheme[type].}
@defproc[(make-cvector* [cptr any/c][type ctype?][length exact-nonnegative-integer?]) cvector?]{
Constructs a C vector using an existing pointer object. This
operation is not safe, so it is intended to be used in specific
situations where the @scheme[type] and @scheme[length] are known.}
@; ------------------------------------------------------------
@section{SRFI-4 Vectors}
SRFI-4 vectors are similar to C vectors (see
@secref["foreign:cvector"]), except that they define different types
of vectors, each with a hard-wired type.
An exception is the @schemeidfont{u8} family of bindings, which are
just aliases for byte-string bindings: @scheme[make-u8vector],
@scheme[u8vector]. @scheme[u8vector?], @scheme[u8vector-length],
@scheme[u8vector-ref], @scheme[u8vector-set!],
@scheme[list->u8vector], @scheme[u8vector->list].
@(begin
(require (for-syntax scheme/base))
(define-syntax (srfi-4-vector stx)
(syntax-case stx ()
[(_ id elem)
#'(srfi-4-vector/desc id elem
"Like " (scheme make-vector) ", etc., but for " (scheme elem) " elements.")]))
(define-syntax (srfi-4-vector/desc stx)
(syntax-case stx ()
[(_ id elem . desc)
(let ([mk
(lambda l
(datum->syntax
#'id
(string->symbol
(apply string-append
(map (lambda (i)
(if (identifier? i)
(symbol->string (syntax-e i))
i))
l)))
#'id))])
(with-syntax ([make (mk "make-" #'id "vector")]
[vecr (mk #'id "vector")]
[? (mk #'id "vector?")]
[length (mk #'id "vector-length")]
[ref (mk #'id "vector-ref")]
[! (mk #'id "vector-set!")]
[list-> (mk "list->" #'id "vector")]
[->list (mk #'id "vector->list")]
[_vec (mk "_" #'id "vector")])
#`(begin
(defproc* ([(make [len exact-nonnegative-integer?]) ?]
[(vecr [val number?] (... ...)) ?]
[(? [v any/c]) boolean?]
[(length [vec ?]) exact-nonnegative-integer?]
[(ref [vec ?][k exact-nonnegative-integer?]) number?]
[(! [vec ?][k exact-nonnegative-integer?][val number?]) void?]
[(list-> [lst (listof number?)]) ?]
[(->list [vec ?]) (listof number?)])
. desc)
;; Big pain: make up relatively-correct source locations
;; for pieces in the _vec definition:
(defform* [#,(datum->syntax
#'_vec
(cons #'_vec
(let loop ([l '(mode type maybe-len)]
[col (+ (syntax-column #'_vec)
(syntax-span #'_vec)
1)]
[pos (+ (syntax-position #'_vec)
(syntax-span #'_vec)
1)])
(if (null? l)
null
(let ([span (string-length (symbol->string (car l)))])
(cons (datum->syntax
#'_vec
(car l)
(list (syntax-source #'_vec)
(syntax-line #'_vec)
col
pos
span))
(loop (cdr l)
(+ col 1 span)
(+ pos 1 span)))))))
(list (syntax-source #'_vec)
(syntax-line #'_vec)
(sub1 (syntax-column #'vec))
(sub1 (syntax-position #'vec))
10))
_vec]
"Like " (scheme _cvector) ", but for vectors of " (scheme elem) " elements."))))])))
@defform*[[(_u8vector mode type maybe-len)
_u8vector]]{
Like @scheme[_cvector], but for vectors of @scheme[_byte] elements.}
@srfi-4-vector[s8 _int8]
@srfi-4-vector[s16 _int16]
@srfi-4-vector[u16 _uint16]
@srfi-4-vector[s32 _int32]
@srfi-4-vector[u32 _uint32]
@srfi-4-vector[s64 _int64]
@srfi-4-vector[u64 _uint64]
@srfi-4-vector[f32 _float]
@srfi-4-vector[f64 _double*]

View File

@ -0,0 +1,26 @@
#lang scribble/doc
@(require "utils.ss")
@title{PLT Foreign Interface Manual}
@defmodule[scheme/foreign]
The @schememodname[scheme/foreign] library enables the direct use of
C-based APIs within Scheme programs---without writing any new C
code). From the Scheme perspective, functions and data with a C-based
API are @idefterm{foreign}, hence the term @defterm{foreign
interface}. Furthermore, since most APIs consist mostly of functions,
the foreign interface is sometimes called a @defterm{foreign function
interface}, abbreviated @deftech{FFI}.
@table-of-contents[]
@include-section["intro.scrbl"]
@include-section["libs.scrbl"]
@include-section["types.scrbl"]
@include-section["pointers.scrbl"]
@include-section["misc.scrbl"]
@include-section["derived.scrbl"]
@include-section["unexported.scrbl"]
@index-section[]

View File

@ -0,0 +1,4 @@
(module info setup/infotab
(define name "Scribblings: FFI")
(define scribblings '(("foreign.scrbl" (multi-page main-doc)))))

View File

@ -0,0 +1,40 @@
#lang scribble/doc
@(require "utils.ss")
@title[#:tag "intro"]{Overview}
Although using the FFI requires writing no new C code, it provides
very little insulation against the issues that C programmer faces
related to safety and memory management. An FFI programmer must be
particularly aware of memory management issues for data that spans the
Scheme--C divide. Thus, this manual relies in many ways on the
information in @|InsideMzScheme|, which defines how PLT Scheme
interacts with C APIs in general.
Since using the FFI entails many safety concerns that Scheme
programmers can normally ignore, merely importing
@schememodname[scheme/foreign] with @scheme[(require scheme/foreign)]
does not import all of the FFI functionality. Only safe functionality
is immediately imported. For example, @scheme[ptr-equal?] can never
cause memory corruption or an invalid memory access, so it is
immediately available on import.
Use @scheme[(#, @indexed-scheme[unsafe!])] at the top-level of a
module that imports @schememodname[scheme/foreign] to make unsafe
features accessible. (For additional safety, the @scheme[unsafe!] is
itself protected; see @secref[#:doc '(lib
"scribblings/reference/reference.scrbl") "modprotect"].) Using this
macro should be considered as a declaration that your code is itself
unsafe, therefore can lead to serious problems in case of bugs: it is
your responsibility to provide a safe interface.
In rare cases, you might want to provide an @italic{unsafe} interface
hat builds on the unsafe features of the FFI. In such cases, use the
@indexed-scheme[provide*] macro with @scheme[unsafe] bindings, and use
@indexed-scheme[define-unsafer] to provide an @scheme[unsafe!]-like macro
that will make these bindings available to importers of your library.
Providing users with unsafe operations without using this facility
should be considered a bug in your code.
For examples of common FFI usage patterns, see the defined interfaces
in the @filepath{ffi} collection.

View File

@ -0,0 +1,137 @@
#lang scribble/doc
@(require "utils.ss"
(for-syntax setup/dirs))
@title{Loading Foreign Libraries}
The FFI is normally used by extracting functions and other objects
from @as-index{shared objects} (a.k.a. @defterm{@as-index{shared
libraries}} or @defterm{@as-index{dynamically loaded libraries}}). The
@scheme[ffi-lib] function loads a shared object.
@defproc[(ffi-lib [path (or/c path-string? false/c)]
[version (or/c string? (listof string?) false/c) #f]) any]{
Returns an foreign-library value. If @scheme[path] is a path, the
result represents the foreign library, which is opened in an
OS-specific way (using @cpp{LoadLibrary} under Windows, and
@cpp{dlopen} under Unix and Mac OS X).
The path is not expected to contain the library suffix, which is added
according to the current platform. If adding the suffix fails,
several other filename variations are tried --- retrying without an
automatically added suffix, and using a full path of a file if it
exists relative to the current directory (since the OS-level library
function usually searches, unless the library name is an absolute
path). An optional @scheme[version] string can be supplied, which is
appended to the name after any added suffix. If you need any of a few
possible versions, use a list of version strings, and @scheme[ffi-lib]
will try all of them.
If @scheme[path] is @scheme[#f], then the resulting foreign-library
value represents all libraries loaded in the current process,
including libraries previouly opened with @scheme[ffi-lib]. In
particular, use @scheme[#f] to access C-level functionality exported
by the run-time system (as described in @|InsideMzScheme|).
Note: @scheme[ffi-lib] tries to look for the library file in a few
places like the PLT libraries (see @scheme[get-lib-search-dirs]), a
relative path, or a system search. However, if @cpp{dlopen} cannot
open a library, there is no reliable way to know why it failed, so if
all path combinations fail, it will raise an error with the result of
@cpp{dlopen} on the unmodified argument name. For example, if you
have a local @filepath{foo.so} library that cannot be loaded because
of a missing symbol, using @scheme[(ffi-lib "foo.so")] will fail with
all its search options, most because the library is not found, and
once because of the missing symbol, and eventually produce an error
message that comes from @cpp{dlopen("foo.so")} which will look like
the file is not found. In such cases try to specify a full or
relative path (containing slashes, e.g., @filepath{./foo.so}).}
@defproc[(ffi-lib? [v any/c]) boolean>]{
Returns @scheme[#t] if @scheme[v] is the result of @scheme[ffi-lib],
@scheme[#f] otherwise.}
@defproc[(get-ffi-obj [objname (or/c string? bytes? symbol?)]
[lib (or/c ffi-lib? path-string? false/c)]
[type ctype?]
[failure-thunk (or/c (-> any) false/c) #f])
any]{
Looks for the given object name @scheme[objname] in the given
@scheme[lib] library. If @scheme[lib] is not a foreign-library value
produced by @scheme[ffi-lib], it is converted to one by calling
@scheme[ffi-lib]. If @scheme[objname] is found in @scheme[lib], it is
converted to Scheme using the given @scheme[type]. Types are described
in @secref["types"]; in particular the @scheme[get-ffi-obj] procedure
is most often used with function types created with @scheme[_fun].
Keep in mind that @scheme[get-ffi-obj] is an unsafe procedure; see
@secref["intro"] for details.
If the object is not found, and @scheme[failure-thunk] is provided, it is
used to produce a return value. For example, a failure thunk can be
provided to report a specific error if an object is not found:
@schemeblock[
(define foo
(get-ffi-obj "foo" foolib (_fun _int -> _int)
(lambda ()
(error 'foolib
"installed foolib does not provide \"foo\""))))
]
The default (also when @scheme[failure-thunk] is provided as @scheme[#f]) is to
raise an exception.}
@defproc[(set-ffi-obj! [objname (or/c string? bytes? symbol?)]
[lib (or/c ffi-lib? path-string? false/c)]
[type ctype?]
[new any/c])
void?]{
Looks for @scheme[objname] in @scheme[lib] similarly to
@scheme[get-ffi-obj], but then it stores the given @scheme[new] value
into the library, converting it to a C value. This can be used for
setting library customization variables that are part of its
interface, including Scheme callbacks.}
@defproc[(make-c-parameter [objname (or/c string? bytes? symbol?)]
[lib (or/c ffi-lib? path-string? false/c)]
[type ctype?])
(and/c (-> any)
(any/c -> void?))]{
Returns a parameter-like procedure that can either references the
specified foreign value, or set it. The arguments are handled as in
@scheme[get-ffi-obj].
A parameter-like function is useful in case Scheme code and library
code interact through a library value. Although
@scheme[make-c-parameter] can be used with any time, it is not
recommended to use this for foreign functions, since each reference
through the parameter will construct the low-level interface before the
actual call.}
@defform[(define-c id lib-expr type-expr)]{
Defines @scheme[id] behave like a Scheme binding, but @scheme[id] is
actually redirected through a parameter-like procedure created by
@scheme[make-c-parameter]. The @scheme[id] is used both for the Scheme
binding and for the foreign object's name.}
@defproc[(ffi-obj-ref [objname (or/c string? bytes? symbol?)]
[lib (or/c ffi-lib? path-string? false/c)]
[failure-thunk (or/c (-> any) false/c) #f])
any]{
Returns a pointer object for the specified foreign object. This
procedure is for rare cases where @scheme[make-c-parameter] is
insufficient, because there is no type to cast the foreign object to
(e.g., a vector of numbers).}

View File

@ -0,0 +1,66 @@
#lang scribble/doc
@(require "utils.ss")
@title{Miscellaneous Support}
@defproc[(regexp-replaces [objname (or/c string? bytes? symbol?)]
[substs (listof (list regexp? string?))])
string?]{
A function that is convenient for many interfaces where the foreign
library has some naming convention that you want to use in your
interface as well. The @scheme[objname] argument can be any value
that will be used to name the foreign object; it is first converted
into a string, and then modified according to the given
@scheme[substs] list in sequence, where each element in this list is a
list of a regular expression and a substitution string. Usually,
@scheme[regexp-replace*] is used to perform the substitution, except
for cases where the regular expression begins with a @litchar{^} or
ends with a @litchar{$}, in which case @scheme[regexp-replace] is
used.
For example, the following makes it convenient to define Scheme
bindings such as @scheme[foo-bar] for foreign names like
@scheme[MyLib_foo_bar]:
@schemeblock[
(define mylib (ffi-lib "mylib"))
(define-syntax defmyobj
(syntax-rules (:)
[(_ name : type ...)
(define name
(get-ffi-obj
(regexp-replaces 'name '((#rx"-" "_")
(#rx"^" "MyLib_")))
mylib (_fun type ...)))]))
(defmyobj foo-bar : _int -> _int)
]}
@defproc[(list->cblock [lst list>][type ctype?]) any]{
Allocates a memory block of an appropriate size, and initializes it
using values from @scheme[lst] and the given @scheme[type]. The
@scheme[lst] must hold values that can all be converted to C values
according to the given @scheme[type].}
@defproc[(cblock->list [cblock any/c][type ctype?][length nonnegative-exact-integer?])
list?]{
Converts C @scheme[cblock], which is a vector of @scheme[type]s, to a
Scheme list. The arguments are the same as in the
@scheme[list->cblock]. The @scheme[length] must be specified because
there is no way to know where the block ends.}
@defproc[(vector->cblock [vector any/c][type type?]) any]{
Like @scheme[list->cblock], but for Scheme vectors.}
@defproc[(cblock->vector [cblock any/c][type ctype?][length nonnegative-exact-integer?])
vector?]{
Like @scheme[cblock->vector], but for Scheme vectors.}

View File

@ -0,0 +1,284 @@
#lang scribble/doc
@(require "utils.ss")
@title[#:tag "foreign:pointer-funcs"]{Pointer Functions}
@;{
@defproc[(cpointer? [v any/c]) boolean?]{
Returns @scheme[#t] if @scheme[v] is a C pointer or a value that can
be used as a pointer: @scheme[#f] (used as a @cpp{NULL} pointer), byte
strings (used as memory blocks), some additional internal objects
(@scheme[ffi-obj]s and callbacks, see @secref["c-only"]). Returns
@scheme[#f] for other values.}
\scmutilsectionO{ptr-ref}{cptr ctype}{\Optional{'abs} offset}{procedure}
\scmutilsection{ptr-set!}{cptr ctype \Optional{\Optional{'abs} offset} value}{procedure}
The @scheme[pre-ref] procedure return the object referenced by
@var{cptr}, using the given @var{ctype}. The @scheme[ptr-set!]\
procedure stores the @var{value} in the memory @var{cptr} points to, using
the given @var{ctype} for the conversion, and returns @|void-const|.
In each case, @var{offset} defaults to $0$ (which is the only value
that should be used with @scheme[ffi-obj] objects, see
section~\ref{foreign:c-only}). If an @var{offset} index is given, the
value is stored at that location, considering the pointer as a vector
of @var{ctype}s --- so the actual address is the pointer plus the size
of @var{ctype} multiplied by @var{offset}. In addition, a @var{'abs}
flag can be used to use the @var{offset} as counting bytes rather then
increments of the specified @var{ctype}.
Beware that the @scheme[ptr-ref] and @scheme[ptr-set!]\ procedure do
not keep any meta-information on how pointers are used. It is the
programmer's responsibility to use this facility only when
appropriate. For example, on a little-endian machine:
%
@schemeblock[
> (define block (malloc _int 5))
> (ptr-set! block _int 0 196353)
> (map (lambda (i) (ptr-ref block _byte i)) '(0 1 2 3))
(1 255 2 0)
]
%
In addition, @scheme[ptr-ref] and @scheme[ptr-set!]\ cannot detect
when offsets are beyond an object's memory bounds; out-of-bounds
access can easily lead to a segmentation fault or memory corruption.
@defproc[(ptr-equal? [cptr$_1$ any/c][cptr$_2$ any/c]) any]
Compares the values of the two pointers. (Note that two different Scheme
pointer objects can contain the same pointer.)
@defproc[(ptr-add [cptr any/c][offset-k nonnegative-exact-integer?][ctype any/c #f]) any]
Returns a cpointer that is like @var{cptr} offset by @var{offset-k}
instances of @var{ctype}. If @var{ctype} is not provided, @var{cptr}
is offset by @var{offset-k} bytes.
The resulting cpointer keeps the base pointer and offset separate. The two
pieces are combined at the last minute before any operation on the pointer,
such as supplying the pointer to a foreign function. In particular, the pointer
and offset are not combined until after all allocation leading up to a
foreign-function call; if the called function does not itself call anything
that can trigger a garbage collection, it can safey use pointers that are
offset into the middle of a GCable object.
@defproc[(offset-ptr? [cptr any/c]) any]
A predicate for cpointers that have an offset, such as pointers that were
created using @scheme[ptr-add]. Returns @scheme[#t] even if such an offset
happens to be 0. Returns @scheme[#f] for other cpointers and non-cpointers.
@defproc[(ptr-offset [cptr any/c]) any]
Returns the offset of a pointer that has an offset. (The resulting offset is
always in bytes.)
@defproc[(set-ptr-offset! [cptr any/c][offset-k nonnegative-exact-integer?][ctype any/c #f]) any]
Sets the offset component of an offset pointer. The arguments are used in the
same way as @scheme[ptr-add]. Raises an error if it is given a pointer that
has no offset.
@defproc[(ptr-add! [cptr any/c][offset-k nonnegative-exact-integer?][ctype any/c #f]) any]
Like @scheme[ptr-add], but destructively modifies the offset contained in a
pointer. (This can also be done using @scheme[ptr-offset] and
@scheme[set-ptr-offset!].)
@defproc[(cpointer-tag [cptr any/c]) any]
Returns the Scheme object that is the tag of the given @var{cptr} pointer.
@defproc[(set-cpointer-tag! [cptr any/c][tag any/c]) any]
Sets the tag of the given @var{cptr}. The @var{tag} argument can be
any arbitrary value; other pointer operations ignore it. When a
cpointer value is printed, its tag is shown if it is a symbol, a byte
string, a string. In addition, if the tag is a pair holding one of
these in its @scheme[car], the @scheme[car] is shown (so that the tag
can contain other information).
\scmutilsection{memmove}{cptr \Optional{offset-k}
src-cptr \Optional{src-offset-k}
count-k \Optional{ctype}}
Copies to @var{cptr} from @var{src-cptr}. The destination pointer can be
offset by an optional @var{offset-k}, which is in bytes if @var{ctype}
is not supplied, or in @var{ctype} instances when supplied.
The source pointer can be similarly offset by @var{src-offset-k}.
The number of bytes copied from source to destination is determined by @var{count-k},
which is also in bytes if @var{ctype} is not supplied, or in @var{ctype}
instances when supplied.
\scmutilsection{memcpy}{cptr \Optional{offset-k}
src-cptr \Optional{src-offset-k}
count-k \Optional{count-ctype}}
Like @scheme[memmove], but the result is
undefined if the destination and source overlap.
\scmutilsection{memset}{cptr \Optional{offset-k}
byte
count-k \Optional{count-ctype}}
Similar to @scheme[memmove], but the destination is uniformly filled with
@var{byte} (i.e., an exact integer between 0 and 255 includive).
%------------------------------------------------------------
@section{Memory Management}
For general information on C-level memory management with MzScheme, see
{\InsideMzSchemeManual}.
\scmutilsection{malloc}{bytes-or-type
\Optional{type-or-bytes}
\Optional{cptr}
\Optional{mode} \Optional{'fail-ok}}{procedure}
Allocates a memory block of a specified size using a specified allocation. The result is a
@scheme[cpointer] to the allocated memory. The four arguments can appear in
any order since they are all different types of Scheme objects; a
size specification is required at minimum:
@itemize{
@item{If a C type @var{bytes-or-type} is given, its size is used to the block
allocation size.}
@item{If an integer @var{bytes-or-type} is given, it specifies the required
size in bytes.}
@item{If both @var{bytes-or-type} and @var{type-or-bytes} are given, then the
allocated size is for a vector of values (the multiplication of the size of
the C type and the integer).}
@item{If a @var{cptr} pointer is given, its contents is copied to the new
block, it is expected to be able to do so.}
@item{A symbol @var{mode} argument can be given, which specifies what
allocation function to use. It should be one of @indexed-scheme['nonatomic] (uses
@cpp{scheme_malloc} from MzScheme's C API), @indexed-scheme['atomic] (@cpp{scheme_malloc_atomic}),
@indexed-scheme['stubborn] (@cpp{scheme_malloc_stubborn}), @indexed-scheme['uncollectable]
(@cpp{scheme_malloc_uncollectable}), @indexed-scheme['eternal] ({\tt
scheme_malloc_eternal}), @indexed-scheme['interior]
(@cpp{scheme_malloc_allow_interior}), @indexed-scheme['atomic-interior]
(@cpp{scheme_malloc_atomic_allow_interior}), or @indexed-scheme['raw] (uses the
operating system's @cpp{malloc}, creating a GC-invisible block).}
@item{If an additional @indexed-scheme['failok] flag is given, then {\tt
scheme_malloc_fail_ok} is used to wrap the call.}
}
If no mode is specified, then @scheme['nonatomic] allocation is used
when the type is any pointer-based type, and @scheme['atomic]
allocation is used otherwise.
@defproc[(free [cpointer any/c]) any]
Uses the operating system's @cpp{free} function for
@scheme['raw]-allocated pointers, and for pointers that a foreign
library allocated and we should free. Note that this is useful as
part of a finalizer (see below) procedure hook (e.g., on the Scheme
pointer object, freeing the memory when the pointer object is
collected, but beware of aliasing).
@defproc[(end-stubborn-change [cpointer any/c]) any]
Uses @cpp{scheme_end_stubborn_change} on the given stubborn-allocated
pointer (see {\InsideMzSchemeManual}).
@defproc[(malloc-immobile-cell [v any/c]) any]
Allocates memory large enough to hold one arbitrary (collectable)
Scheme value, but that is not itself collectable or moved by the
memory manager. The cell is initialized with @var{v}; use the type
@scheme[_scheme] with @scheme[ptr-ref] and @scheme[ptr-set!] to get
or set the cell's value. The cell must be explicitly freed with
@scheme[free-immobile-cell].
@defproc[(free-immobile-cell [cpointer any/c]) any]
Frees an immobile cell created by @scheme[malloc-immobile-cell].
%% *** Documentation for the disabled C code. A Scheme impl. is used now.
%% @defproc[(register-finalizer [cptr any/c][finalizer any/c]['pointer any/c #f]) any]
%%
%% Registers a finalizer procedure @var{finalizer-proc} with the given @var{cptr}
%% object. The finalizer is called by the primitive GC finalizer mechanism, make
%% sure no references to the object are recreated. Using @scheme[#f] for
%% @var{finalizer-proc} means erase the existing finalizer, if any. The finalizer
%% is registered for the Scheme pointer object --- be careful with aliasing.
%%
%% If an optional @var{'pointer} symbol argument is used, the finalizer is
%% registered with the actual pointer rather than the Scheme object. The
%% procedure gets a new C pointer object that points to the collected pointer.
%% This should be used only with pointers that the GC can access.
@defproc[(register-finalizer [obj any/c][finalizer any/c]) any]
Registers a finalizer procedure @var{finalizer-proc} with the given @var{obj}
which can be any Scheme (GC-able) object. The finalizer is registered with a
will executor (see \MzSecRef{willexecutor}); it is invoked when @var{obj} is
about to be collected. (This is done by a thread that is in charge of
triggering these will executors.)
This is mostly intended to be used with cpointer objects (for freeing
unused memory that is not under GC control), but it can be used with
any Scheme object --- even ones that have nothing to do with foreign
code. Note, however, that the finalizer is registered for the
@italic{Scheme} object. If you intend to free a pointer object, then you
must be careful to not register finalizers for two cpointers that
point to the same address. Also, be careful to not make the finalizer
a closure that holds on to the object.
For example, suppose that you're dealing with a foreign function that returns a C
string that you should free. Here is an attempt at creating a suitable type:
%
@schemeblock[
(define _bytes/free
(make-ctype _pointer
#f ; a Scheme bytes can be used as a pointer
(lambda (x)
(let ([b (make-byte-string x)])
(register-finalizer x free)
b))))
]
%
This is wrong: the finalizer is registered for @scheme[x], which is no longer
needed once the byte string is created. Changing this to register the
finalizer for @scheme[b] correct this problem, but then @scheme[free] will be
invoked on it instead of on @scheme[x]. In an attempt to fix this, we will be
careful and print out a message for debugging:
%
@schemeblock[
(define _bytes/free
(make-ctype _pointer
#f ; a Scheme bytes can be used as a pointer
(lambda (x)
(let ([b (make-byte-string x)])
(register-finalizer b
(lambda (_)
(printf "Releasing ~s\n" b)
(free x)))
b))))
]
%
but we never see any printout --- the problem is that the finalizer is a
closure that keeps a reference to @scheme[b]. To fix this, you should use the
input argument to the finalizer. Simply changing the @scheme[_] to @scheme[b]
will solve this problem. (Removing the debugging message also avoids the problem,
since the finalization procedure would then not close over @scheme[b].)
@defproc[(make-sized-byte-string [cptr any/c][length any/c]) any]
Returns a byte string made of the given pointer and the given
length. No copying is done. This can be used as an alternative to make
pointer values accessible in Scheme when the size is known.
If @var{cptr} is an offset pointer created by @scheme[ptr-add], the
offset is immediately added to the pointer. Thus, this function cannot
be used with @scheme[ptr-add] to create a substring of a Scheme byte
string, because the offset pointer would be to the middle of a
collectable object (which is not allowed).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
}

View File

@ -0,0 +1,777 @@
#lang scribble/doc
@(require "utils.ss")
@title[#:tag "types" #:style 'toc]{C Types}
@deftech{C types} are the main concept of the @tech{FFI}, either
primitive types or user-defined types. The @tech{FFI} deals with
primitive types internally, converting them to and from C types. A
user type is defined in terms of existing primitive and user types,
along with conversion functions to and from the existing types.
@local-table-of-contents[]
@; ----------------------------------------------------------------------
@section{Type Constructors}
@defproc[(make-ctype [type ctype?]
[scheme-to-C (or/c false/c (any/c . -> . any))]
[C-to-scheme (or/c false/c (any/c . -> . any))])
cttype?]{
Creates a new @tech{C type} value, with the given conversions
functions. The conversion functions can be @scheme[#f] meaning that
there is no conversion for the corresponding direction. If both
functions are @scheme[#f], @scheme[type] is returned.}
@defproc[(ctype? [v any/c]) boolean?]{
Returns @scheme[#t] if @scheme[v] is a @tech{C type}, @scheme[#f]
otherwise.}
@defproc*[([(ctype-sizeof [type ctype?]) nonnegative-exact-integer?]
[(ctype-alignof [ctype ctype?]) nonnegative-exact-integer?])]{
Returns the size or alignment of a given @scheme[type] for the current
platform.}
@defproc[(compiler-sizeof [sym symbol?]) nonnegative-exact-integer?]{
Possible values for @scheme[symbol] are @scheme['int], @scheme['char],
@scheme['short], @scheme['long], @scheme['*], @scheme['void],
@scheme['float], @scheme['double]. The result is the size of the
correspond type according to the C @cpp{sizeof} operator for the
current platform. The @scheme[compiler-sizeof] operation should be
used to gather information about the current platform, such as
defining alias type like @scheme[_int] to a known type like
@scheme[_int32].}
@; ----------------------------------------------------------------------
@section{Numeric Types}
@defthing*[([_int8 ctype?]
[_sint8 ctype?]
[_uint8 ctype?]
[_int16 ctype?]
[_sint16 ctype?]
[_uint16 ctype?]
[_int32 ctype?]
[_sint32 ctype?]
[_uint32 ctype?]
[_int64 ctype?]
[_sint64 ctype?]
[_uint64 ctype?])]{
The basic integer types at various sizes. The @schemeidfont{s} or
@schemeidfont{u} prefix specifies a signed or an unsigned integer,
respectively; the ones with no prefix are signed.}
@defthing*[([_byte ctype?]
[_sbyte ctype?]
[_ubyte ctype?]
[_short ctype?]
[_sshort ctype?]
[_ushort ctype?]
[_int ctype?]
[_sint ctype?]
[_uint ctype?]
[_word ctype?]
[_sword ctype?]
[_uword ctype?]
[_long ctype?]
[_slong ctype?]
[_ulong ctype?])]{
Aliases for basic integer types. The @scheme[_byte] aliases correspond
to @scheme[_int8]. The @scheme[_short] and @scheme[_word] aliases
correspond to @scheme[_int16]. The @scheme[_int] aliases correspond to
@scheme[_int32]. The @scheme[_long] aliases correspond to either
@scheme[_int32] or @scheme[_int64], depending on the platform.}
@defthing*[([_fixnum ctype?]
[_ufixnum ctype?])]{
For cases where speed matters and where you know that the integer is
small enough, the types @scheme[_fixnum] and @scheme[_ufixnum] are
similar to @scheme[_long] and @scheme[_ulong] but assume that the
quantities fit in PLT Scheme's immediate integers (i.e., not bignums).}
@defthing*[([_fixint ctype?]
[_ufixint ctype?])]{
Like @scheme[_fixnum] and @scheme[_ufixnum], but coercions from C are
checked to be in range.}
@defthing*[([_float ctype?]
[_double ctype?]
[_double* ctype?])]{
The @scheme[_float] and @scheme[_double] types represent the
corresponding C types. The type @scheme[_double*] that implicitly
coerces any real number to a C @cpp{double}.}
@; ------------------------------------------------------------
@section{Other Atomic Types}
@defthing[_bool ctype?]{
Translates @scheme[#f] to a @scheme[0] @scheme[_int], and any other
value to @scheme[1].}
@defthing[_void ctype?]{
Indicates a Scheme @|void-const| return value, and it cannot be used
to translate values to C. This type cannot be used for function
inputs.}
@; ------------------------------------------------------------
@section{String Types}
@subsection{Primitive String Types}
The five primitive string types corerspond to cases where a C
representation matches MzScheme's representation without encodings.
The form @scheme[_bytes] form can be used type for Scheme byte
strings, which corresponds to C's @cpp{char*} type. In addition to
translating byte strings, @scheme[#f] corresponds to the @cpp{NULL}
pointer.
@defthing[_string/ucs-4 ctype?]{
A type for Scheme's native Unicode strings, which are in UCS-4 format.
These correspond to the C @cpp{mzchar*} type used by PLT Scheme.}
@defthing[_string/utf-16 ctype?]{
Unicode strings in UTF-16 format.}
@defthing[_path ctype?]{
Simple @cpp{char*} strings, corresponding to Scheme's paths.}
@defthing[_symbol ctype?]{
Simple @cpp{char*} strings as Scheme symbols (encoded in UTF-8).
Return values using this type are interned as symbols.}
@subsection{Fixed Auto-Converting String Types}
@defthing*[([_string/utf-8 ctype?]
[_string/latin-1 ctype?]
[_string/locale ctype?])]{
Types that correspond to (character) strings on the Scheme side and
@cpp{char*} strings on the C side. The brige between the two requires
a transformation on the content of the string. As usual, the types
treat @scheme[#f] as @cpp{NULL} and vice-versa.}
@defthing*[([_string*/utf-8 ctype?]
[_string*/latin-1 ctype?]
[_string*/locale ctype?])]{
Similar to @scheme[_string/utf-8], etc., but accepting a wider range
of values: Scheme byte strings are allowed and passed as is, and
Scheme paths are converted using @scheme[path->bytes].}
@subsection{Variable Auto-Converting String Type}
The @scheme[_string/ucs-4] type is rarely useful when interacting with
foreign code, while using @scheme[_bytes] is somewhat unnatural, since
it forces Scheme programmers to use byte strings. Using
@scheme[_string/utf-8], etc., meanwhile, may prematurely commit to a
particular encoding of strings as bytes. The @scheme[_string] type
supports conversion between Scheme strings and @cpp{char*} strings
using a parameter-determined conversion.
@defthing[_string ctype?]{
Expands to a use of the @scheme[default-_string-type] parameter. The
parameter's value is consulted when @scheme[_string] is evaluated, so
the parameter should be set before any interface definition that uses
@scheme[_string].}
@defparam[default-_string-type type ctype?]{
A parameter that determines the current meanging of @scheme[_string].
It is initially set to @scheme[_string/*utf-8]. If you change it, do
so @italic{before} interfaces are defined.}
@subsection{Other String Types}
@defthing[_file ctype?]{
Like @scheme[_path], but when values go from Scheme to C,
@scheme[cleanse-path] is used on the given value. As an output value,
it is identical to @scheme[_path].}
@defthing[_bytes/eof ctype?]{
Similar to the @scheme[_bytes] type, except that a foreign return
value of @cpp{NULL} is translated to a Scheme @scheme[eof] value.}
@defthing[_string/eof ctype?]{
Similar to the @scheme[_string] type, except that a foreign return
value of @cpp{NULL} is translated to a Scheme @scheme[eof] value.}
@; ------------------------------------------------------------
@section{Pointer Types}
@defthing[_pointer ctype?]{
Corresponds to Scheme ``C pointer'' objects. These pointers can have
an arbitrary Scheme object attached as a type tag. The tag is ignored
by built-in functionality; it is intended to be used by interfaces.
See @secref["tagged-pointers"] for creating pointer types that use
these tags for safety.}
@defthing[_scheme ctype?]{
This type can be used with any Scheme object; it corresponds to the
@cpp{Scheme_Object*} type of PLT Scheme's C API (see
@|InsideMzScheme|). It is useful only for libraries that are aware of
PLT Scheme's C API.}
@defthing[_fpointer ctype?]{
Similar to @scheme[_pointer], except that it should be used with
function pointers. Using these pointers avoids one dereferencing,
which is the proper way of dealing with function pointers. This type
should be used only in rare situations where you need to pass a
foreign function pointer to a foreign function; using a
@scheme[_cprocedure] type is possible for such situations, but
inefficient, as every call will go through Scheme unnecessarily.
Otherwise, @scheme[_cprocedure] should be used (it is based on
@scheme[_fpointer]).}
@; ------------------------------------------------------------
@section[#:tag "foreign:procedures"]{Function Types}
@defproc[(_cprocedure [input-types (list ctype?)]
[output-type ctype?]
[wrapper (or false/c (procedure? . -> . procedure?)) #f]) any]{
A type constructor that creates a new function type, which is
specified by the given @scheme[input-types] list and @scheme[output-type].
Usually, the @scheme[_fun] syntax (described below) should be used
instead, since it manages a wide range of complicated cases.
The resulting type can be used to reference foreign functions (usually
@scheme[ffi-obj]s, but any pointer object can be referenced with this type),
generating a matching foreign callout object. Such objects are new primitive
procedure objects that can be used like any other Scheme procedure.
A type created with @scheme[_cprocedure] can also be used for passing
Scheme procedures to foreign functions, which will generate a foreign
function pointer that calls the given Scheme procedure when it is
used. There are no restrictions on the Scheme procedure; in
particular, its lexical context is properly preserved.
The optional @scheme[wrapper-proc], if provided, is expected to be a function that
can change a callout procedure: when a callout is generated, the wrapper is
applied on the newly created primitive procedure, and its result is used as the
new function. Thus, @scheme[wrapper-proc] is a hook that can perform various argument
manipulations before the foreign function is invoked, and return different
results (for example, grabbing a value stored in an `output' pointer and
returning multiple values). It can also be used for callbacks, as an
additional layer that tweaks arguments from the foreign code before they reach
the Scheme procedure, and possibly changes the result values too.}
@defform/subs[#:literals (-> :: :)
(_fun maybe-args type-spec ... -> type-spec maybe-wrapper)
([maybe-args code:blank
(code:line (id ...) ::)
(code:line id ::)
(code:line (id ... . id) ::)]
[type-spec type-expr
(id : type-expr)
(type-expr = value-expr)
(id : type-expr = value-expr)]
[maybe-wrapper code:blank
(code:line -> output-expr)])]{
Creates a new function type. The @scheme[_fun] form is a convenient
syntax for the @scheme[_cprocedure] type constructor. In its simplest
form, only the input @scheme[type-expr]s and the output @scheme[type-expr] are
specified, and each types is a simple expression, which creates a
straightforward function type.
In its full form, the @scheme[_fun] syntax provides an IDL-like
language that can be used to create a wrapper function around the
primitive foreign function. These wrappers can implement complex
foreign interfaces given simple specifications. The full form of each
of the type specifications can include an optional label and an
expression. If a @scheme[= value-expr] is provided, then the resulting
function will be a wrapper that calculates the argument for that
position itself, meaning that it does not expect an argument for that
position. The expression can use previous arguments if they were
labeled with @scheme[id :]. In addition, the result of a function
call need not be the value returned from the foreign call: if the
optional @scheme[output-expr] is specified, or if an expression is
provided for the output type, then this specifies an expression that
will be used as a return value. This expression can use any of the
previous labels, including a label given for the output which can be
used to access the actual foreign return value.
In rare cases where complete control over the input arguments is needed, the
wrapper's argument list can be specified as @scheme[args], in any form (including
a `rest' argument). Identifiers in this place are related to type labels, so
if an argument is there is no need to use an expression.
For example,
@schemeblock[
(_fun (n s) :: (s : _string) (n : _int) -> _int)
]
specifies a function that receives an integer and a string, but the
foreign function receives the string first.}
@; ----------------------------------------------------------------------
@subsection[#:tag "foreign:custom-types"]{Custom Function Types}
The behavior of the @scheme[_fun] type can be customized via
@deftech{custom function types}, which are pieces of syntax that can
behave as C types and C type constructors, but they can interact with
function calls in several ways that are not possible otherwise. When
the @scheme[_fun] form is expanded, it tries to expand each of the
given type expressions, and ones that expand to certain keyword-value
lists interact with the generation of the foreign function wrapper.
This expansion makes it possible to construct a single wrapper
function, avoiding the costs involved in compositions of higher-order
functions.
Custom function types are macros that expand to a sequence
@scheme[(_key: _val ...)], where each @scheme[_key:] is from a short list
of known keys. Each key interacts with generated wrapper functions in
a different way, which affects how its corresponding argument is
treated:
@itemize{
@item{@scheme[type:] specifies the foreign type that should be used, if it is
@scheme[#f] then this argument does not participate in the foreign call.}
@item{@scheme[expr:] specifies an expression to be used for arguments of this
type, removing it from wrapper arguments.}
@item{@scheme[bind:] specifies a name that is bound to the original
argument if it is required later (e.g., @scheme[_box] converts its
associated value to a C pointer, and later needs to refer back to
the original box).}
@item{@scheme[1st-arg:] specifies a name that can be used to refer to
the first argument of the foreign call (good for common cases where
the first argument has a special meaning, e.g., for method calls).}
@item{@scheme[prev-arg:] similar to @scheme[1st-arg:], but refers to the
previous argument.}
@item{@scheme[pre:] a pre-foreign code chunk that is used to change the
argument's value.}
@item{@scheme[post:] a similar post-foreign code chunk.}
}
The @scheme[pre:] and @scheme[post:] bindings can be of the form
@scheme[(_id => _expr)] to use the existing value. Note that if the
@scheme[pre:] expression is not @scheme[(_id => _expr)], then it means
that there is no input for this argument to the
@scheme[_fun]-generated procedure. Also note that if a custom type is
used as an output type of a function, then only the @scheme[post:]
code is used.
Most custom types are meaningful only in a @scheme[_fun] context, and
will raise a syntax error if used elsewhere. A few such types can be
used in non-@scheme[_fun] contexts: types which use only
@scheme[type:], @scheme[pre:], @scheme[post:], and no others. Such
custom types can be used outside a @scheme[_fun] by expanding them
into a usage of @scheme[make-ctype], using other keywords makes this
impossible, because it means that the type has specific interaction
with a function call.
@defform[(define-fun-syntax id transformer-expr)]{
Binds @scheme[id] as a @tech{custom function type}. The type is
expanded by applying the procedure produced by
@scheme[transformer-expr] to a use of the @tech{custom function
type}.}
@defidform[_?]{
A @tech{custom function type} that is a marker for expressions that
should not be sent to the foreign function. Use this to bind local
values in a computation that is part of an ffi wrapper interface, or
to specify wrapper arguments that are not sent to the foreign function
(e.g., an argument that is used for processing the foreign output).}
@defform/subs[#:literals (i io io)
(_ptr mode type-expr)
([mode i o io])]{
Creates a C pointer type, where @scheme[mode] indicates input or
output pointers (or both). The @scheme[mode] can be one of the
following:
@itemize{
@item{@scheme[i] --- indicates an @italic{input} pointer argument:
the wrapper arranges for the function call to receive a value that
can be used with the @scheme[type] and to send a pointer to this
value to the foreign function. After the call, the value is
discarded.}
@item{@scheme[o] --- indicates an @italic{output} pointer argument:
the foreign function expects a pointer to a place where it will save
some value, and this value is accessible after the call, to be used
by an extra return expression. If @scheme[_ptr] is used in this
mode, then the generated wrapper does not expect an argument since
one will be freshly allocated before the call.}
@item{@scheme[io] --- combines the above into an
@italic{input/output} pointer argument: the wrapper gets the Scheme
value, allocates and set a pointer using this value, and then
references the value after the call. The ``@scheme[_ptr]'' name can
be confusing here: it means that the foreign function expects a
pointer, but the generated wrapper uses an actual value. (Note that
if this is used with structs, a struct is created when calling the
function, and a copy of the return value is made too---which is
inefficient, but ensures that structs are not modified by C code.)}
}
For example, the @scheme[_ptr] type can be used in output mode to create a
foreign function wrapper that returns more than a single argument. The
following type:
@schemeblock[
(_fun (i : (_ptr o _int))
-> (d : _double)
-> (values d i))
]
creates a function that calls the foreign function with a fresh
integer pointer, and use the value that is placed there as a second
return value.}
@defidform[_box]{
A @tech{custom function type} similar to a @scheme[(_ptr io _type)]
argument, where the input is expected to be a box holding an
appropriate value, which is unboxed on entry and modified accordingly
on exit.}
@defform/subs[(_list mode type maybe-len)
([mode i o io]
[maybe-len code:blank
len-expr])]{
A @tech{custom function type} that is similar to @scheme[_ptr], except
that it is used for converting lists to/from C vectors. The optional
@scheme[len] argument is needed for output values where it is used in
the post code, and in the pre code of an output mode to allocate the
block. In either case, it can refer to a previous binding for the
length of the list which the C function will most likely require.}
@defform[(_vector mode type maybe-len)]{
A @tech{custom function type} like @scheme[_list], except that it uses
Scheme vectors instead of lists.}
@defform*[#:literals (o)
[(_bytes o len-expr)
_bytes]]{
A @tech{custom function type} that can be used by itself as a simple
type for a byte string as a C pointer. Alternatively, the second form
is for a pointer return value, where the size should be explicitly
specified.
There is no need for other modes: input or input/output would be just
like @scheme[_bytes], since the string carries its size information
(there is no real need for the @scheme[o] part of the syntax, but it
is present for consistency with the above macros).}
@defform*[[(_cvector mode type maybe-len)
_cvector]]{
Like @scheme[_bytes], @scheme[_cvector] can be used as a simple type
that corresponds to a pointer that is managed as a safe C vector on
the Scheme side; see @secref["foreign:cvector"]. The longer form
behaves similarly to the @scheme[_list] and @scheme[_vector] custom
types, except that @scheme[_cvector] is more efficient; no Scheme
list or vector is needed.}
@; ------------------------------------------------------------
@section{C Struct Types}
@defproc[(make-cstruct-type [types (listof ctype?)]) ctype?]{
The primitive type constructor for creating new C struct types. These
types are actually new primitive types; they have no conversion
functions associated. The corresponding Scheme objects that are used
for structs are pointers, but when these types are used, the value
that the pointer @italic{refers to} is used, rather than the pointer
itself. This value is basically made of a number of bytes that is
known according to the given list of @scheme[types] list.}
@defproc[(_list-struct [type ctype?] ...+) ctype?]{
A type constructor that builds a struct type using
@scheme[make-cstruct-type] function and wraps it in a type that
marshals a struct as a list of its components. Note that space for
structs must to be allocated; the converter for a
@scheme[_list-struct] type immediately allocates and uses a list from
the allocated space, so it is inefficient. Use @scheme[define-cstruct]
below for a more efficient approach.}
@defform/subs[(define-cstruct id/sup ([field-id type-expr] ...))
[(id/sup _id
(_id super-id))]]{
Defines a new C struct type, but unlike @scheme[_list-struct], the
resulting type deals with C structs in binary form, rather than
marshaling them to Scheme values. The syntax is similar to
@scheme[define-struct], providing accessor functions for raw struct
values (which are pointer objects). The new type uses pointer tags to
guarantee that only proper struct objects are used. The @scheme[_id]
must start with @litchar{_}.
The resulting bindings are as follows:
@itemize{
@item{@scheme[_id] : the new C type for this struct.}
@item{@scheme[_id]@schemeidfont{-pointer}: a pointer type that should
be used when a pointer to values of this struct are used.}
@item{@schemevarfont{id}@schemeidfont{?}: a predicate for the new type.}
@item{@schemevarfont{id}@schemeidfont{-tag}: the tag string object that is
used with instances.}
@item{@schemeidfont{make-}@schemevarfont{id} : a constructor, which expects
an argument for each type.}
@item{@schemevarfont{id}@schemeidfont{-}@scheme[field-id] : an accessor
function for each @scheme[field-id].}
@item{@schemeidfont{set-}@schemevarfont{id}@schemeidfont{-}@scheme[field-id]@schemeidfont{!}
: a mutator function for each @scheme[field-id].}
}
Objects of the new type are actually C pointers, with a type tag that
is a list that contains the string form of @schemevarfont{id}. Since
structs are implemented as pointers, they can be used for a
@scheme[_pointer] input to a foreign function: their address will be
used. To make this a little safer, the corresponding cpointer type is
defined as @scheme[_id]@schemeidfont{-pointer}. The @scheme[_id] type
should not be used when a pointer is expected, since it will cause the
struct to be copied rather than use the pointer value, leading to
memory corruption.
If the first field is itself a cstruct type, its tag will be used in
addition to the new tag. This feature supports common cases of object
inheritance, where a sub-struct is made by having a first field that
is its super-struct. Instances of the sub-struct can be considered as
instances of the super-struct, since they share the same initial
layout. Using the tag of an initial cstruct field means that the same
behavior is implemented in Scheme; for example, accessors and mutators
of the super-cstruct can be used with the new sub-cstruct. See the
example below.
Providing a @scheme[super-id] is shorthand for using an initial field
named @scheme[super-id] and using @schemeidfont{_}@scheme[super-id]]
as its type. Thus, the new struct will use
@schemeidfont{_}@scheme[super-id]'s tag in addition to its own tag,
meaning that instances of @scheme[_id] can be used as instances of
@schemeidfont{_}@scheme[super-id]. Aside from the syntactic sugar,
the constructor function is different when this syntax is used:
instead of expecting a first argument that is an instance of
@schemeidfont{_}@scheme[super-id], the constructor will expect
arguments for each of @schemeidfont{_}@scheme[super-id]'s fields, in
addition for the new fields. This adjustment of the constructor is,
again, in analogy to using a supertype with @scheme[define-struct].
Note that structs are allocated as atomic blocks, which means that the
garbage collector ignores their content. Currently, there is no safe
way to store pointers to GC-managed objects in structs (even if you
keep a reference to avoid collecting the referenced objects, a the 3m
variant's GC will invalidate the pointer's value). Thus, only
non-pointer values and pointers to memory that is outside the GC's
control can be lpaced into struct fields.
As an example, consider the following C code:
@verbatim[#<<EOS
typedef struct { int x; char y; } A;
typedef struct { A a; int z; } B;
A* makeA() {
A *p = malloc(sizeof(A));
p->x = 1;
p->y = 2;
return p;
}
B* makeB() {
B *p = malloc(sizeof(B));
p->a.x = 1;
p->a.y = 2;
p->z = 3;
return p;
}
char gety(A* a) {
return a->y;
}
EOS
]
Using the simple @scheme[_list-struct], you might expect this code to
work:
@schemeblock[
(define makeB
(get-ffi-obj 'makeB "foo.so"
(_fun -> (_list-struct (_list-struct _int _byte) _int))))
(makeB) (code:comment #, @t{should return @scheme['((1 2) 3)]})
]
The problem here is that @cpp{makeB} returns a pointer to the struct rather
than the struct itself. The following works as expected:
@schemeblock[
(define makeB
(get-ffi-obj 'makeB "foo.so" (_fun -> _pointer)))
(ptr-ref (makeB) (_list-struct (_list-struct _int _byte) _int))
]
As described above, @scheme[_list-struct]s should be used in cases where
efficiency is not an issue. We continue using @scheme[define-cstruct], first
define a type for @cpp{A} which makes it possible to use `@cpp{makeA}:
@schemeblock[
(define-cstruct _A ([x _int] [y _byte]))
(define makeA
(get-ffi-obj 'makeA "foo.so"
(_fun -> _A-pointer))) (code:comment #, @t{using @scheme[_A] is a memory-corrupting bug!})
(define a (makeA))
(list a (A-x a) (A-y a))
(code:comment #, @t{produces an @scheme[A] containing @scheme[1] and @scheme[2]})
]
Using @cpp{gety} is also simple:
@schemeblock[
(define gety
(get-ffi-obj 'gety "foo.so"
(_fun _A-pointer -> _byte)))
(gety a) (code:comment #, @t{produces @scheme[2]})
]
We now define another C struct for @cpp{B}, and expose @cpp{makeB}
using it:
@schemeblock[
(define-cstruct _B ([a _A] [z _int]))
(define makeB
(get-ffi-obj 'makeB "foo.so"
(_fun -> _B-pointer)))
(define b (makeB))
]
We can access all values of @scheme[b] using a naive approach:
@schemeblock[
(list (A-x (B-a b)) (A-y (B-a b)) (B-z b))
]
but this is inefficient as it allocates and copies an instance of
`@cpp{A}' on every access. Inspecting the tags @scheme[(cpointer-tag
b)] we can see that @cpp{A}'s tag is included, so we can simply use
its accessors and mutators, as well as any function that is defined to
take an @cpp{A} pointer:
@schemeblock[
(list (A-x b) (A-y b) (B-z b))
(gety b)
]
Constructing a @cpp{B} instance in Scheme requires allocating a
temporary @cpp{A} struct:
@schemeblock[
(define b (make-B (make-A 1 2) 3))
]
To make this more efficient, we switch to the alternative
@scheme[define-cstruct] syntax, which creates a constructor that
expects arguments for both the super fields ands the new ones:
@schemeblock[
(define-cstruct (_B _A) ([z _int]))
(define b (make-B 1 2 3))
]}
@; ------------------------------------------------------------
@section{Enumerations and Masks}
Although the constructors below are describes as procedures,they are
implemented as syntax, so that error messages can report a type name
where the syntactic context implies one.
@defproc[(_enum [symbols list?][basetype ctype? _ufixint]) ctype?]{
Takes a list of symbols and generates an enumeration type. The
enumeration maps between the given @scheme[symbols] and integers,
counting from @scheme[0].
The list @scheme[symbols] can also set the values of symbols by
putting @scheme['=] and an exact integer after the symbol. For
example, the list @scheme['(x y = 10 z)] maps @scheme['x] to
@scheme[0], @scheme['y] to @scheme[10], and @scheme['z] to
@scheme[11].
The @scheme[basetype] argument specifies the base type to use.}
@defproc[(_bitmask [symbols (or symbol? list?)][basetype ctype? _uint]) ctype?]{
Similar to @scheme[_enum], but the resulting mapping translates a list
of symbols to a number and back, using @scheme[bitwise-or]. A single
symbol is equivalent to a list containing just the symbol. The
default @scheme[basetype] is @scheme[_uint], since high bits are often
used for flags.}

View File

@ -0,0 +1,67 @@
#lang scribble/doc
@(require "utils.ss"
(for-label (only-in '#%foreign
ffi-obj ffi-obj? ffi-obj-lib ffi-obj-name
ctype-basetype ctype-scheme->c ctype-c->scheme
ffi-call ffi-callback ffi-callback?)))
@title[#:tag "foreign:c-only"]{Unexported Primitive Functions}
@declare-exporting['#%foreign]
Parts of the @schememodname[scheme/foreign] libray are implemented by
the MzScheme built-in @schememodname['#%foreign] module. The
@schememodname['#%foreign] module is not intended for direct use, but
it exports the following procedures. If you find any of these useful,
please let us know.
@defproc[(ffi-obj [objname (or/c string? bytes? symbol?)]
[lib (or/c ffi-lib? path-string? false/c)])
any]{
Pulls out a foreign object from a library, returning a Scheme value
that can be used as a pointer. If a name is provided instead of a
foreign-library value, @scheme[ffi-lib] is used to create a library
object.}
@defproc*[([(ffi-obj? [x any/c]) boolean?]
[(ffi-obj-lib [obj ffi-obj?]) ffi-lib?]
[(ffi-obj-name [obj ffi-obj?]) string?])]{
A predicate for objects returned by @scheme[ffi-obj], and accessor
functions that return its corresponding library object and name.
These values can also be used as C pointer objects.}
@defproc*[([(ctype-basetype [type ctype?]) (or/c ctype? false/c)]
[(ctype-scheme->c [type ctype?]) procedure?]
[(ctype-c->scheme [type ctype?]) procedure?])]{
Accessors for the components of a C type object, made by
@scheme[make-ctype]. The @scheme[ctype-basetype] selector returns
@scheme[#f] for primitive types (including cstruct types).}
@defproc[(ffi-call [ptr any/c][in-types (listof ctype?)][out-type ctype?]) any]{
The primitive mechanism that creates Scheme ``callout'' values. The
given @scheme[ptr] (any pointer value, including @scheme[ffi-obj]
values) is wrapped in a Scheme-callable primitive function that uses
the types to specify how values are marshaled.}
@defproc[(ffi-callback [proc any/c][in-types any/c][out-type any/c])
ffi-callback?]{
The symmetric counterpart of @scheme[ffi-call]. It receives a Scheme
procedure and creates a callback object, which can also be used as a
pointer. This object can be used as a C-callable function, which
invokes @scheme[proc] using the types to specify how values are
marshaled.}
@defproc[(ffi-callback? [x any/c]) boolean?]{
A predicate for callback values that are created by @scheme[ffi-callback].
}

View File

@ -0,0 +1,8 @@
#lang scheme/base
(require scheme/foreign)
(unsafe!)
(provide (all-defined-out)
(all-from-out scheme/foreign))

View File

@ -0,0 +1,22 @@
#lang scheme/base
(require scribble/manual
scribble/struct
scribble/decode
(for-syntax scheme/base)
(for-label scheme/base
scheme/contract
(except-in "unsafe-foreign.ss" ->)))
(provide cpp
InsideMzScheme
(all-from-out scribble/manual)
(for-label (all-from-out scheme/base
scheme/contract
"unsafe-foreign.ss")))
(define cpp tt)
(define InsideMzScheme
(italic (secref #:doc '(lib "scribblings/inside/inside.scrbl")
"top")))