- c_import(+Header, +Flags, +Functions)
- Import Functions as predicates from Libs based on the declaration
from Header.
- define(:Head, +CSignature)
- Actually link the C function
- c_struct(+Name, +Fields)
- Declare a C structure with name Name. Fields is a list of field
specifications of the form:
Where Type is one of
- A primitive type (
char
, uchar
, ...)
struct(Name)
union(Name)
enum(Name)
- *(Type)
array(Type, Size)
This directive is normally used by c_import/3 to create type
information for structures that are involved in functions that are
imported. This directive may be used explicitly in combination with
the C memory access predicates to read or write memory using C
binary representation.
- c_union(+Name, +Fields)
- Declare a C union with name Name. Fields is a list of fields
using the same conventions as c_struct/2.
- c_type_size_align(:Type, -Size, -Alignment) is det
- True when Type must be aligned at Alignment and is of size Size.
- c_expand_type(:TypeIn, :TypeOut)
- Expand user defined types to arrive at the core type.
- c_current_struct(:Name) is nondet
- c_current_struct(:Name, ?Size, ?Align) is nondet
- Total size of the struct in bytes and alignment restrictions.
- c_current_struct_field(:Name, ?Field, ?Offset, ?Type)
- Fact to provide efficient access to fields
- c_current_union(:Name) is nondet
- c_current_union(:Name, ?Size, ?Align) is nondet
- Total size of the union in bytes and alignment restrictions.
- c_current_union_field(:Name, ?Field, ?Type)
- Fact to provide efficient access to fields
- c_alloc(-Ptr, :TypeAndInit) is det
- Allocate memory for a C object of Type and optionally initialse the
data. TypeAndInit can take several forms:
- A plain type
-
Allocate an array to hold a single object of the given type.
- Type[Count]
-
Allocate an array to hold Count objects of Type.
- Type[] = Init
-
If Init is data that can be used to initialize an array of
objects of Type, allocate an array of sufficient size and
initialize each element with data from Init. The following
combinations of Type and Init are supported:
- char[] = Text
-
Where Text is a valid Prolog representation for text: an
atom, string, list of character codes or list of characters.
The Prolog Unicode data is encoded using the native multibyte
encoding of the OS.
char(Encoding)
[] = Text-
Same as above, using a specific encoding. Encoding is one of
text
(as above), utf8
or iso_latin_1
.
- Type[] = List
-
If Data is a list, allocate an array of the length of the
list and store each element in the corresponding location of the
array.
- Type = Value
-
Same as
Type[] = [Value]
.
- To be done
- - : error generation
- - : support enum and struct initialization from atoms and
dicts.
- c_load(:Location, -Value) is det
- Load a C value indirect from Location. Location is a pointer,
postfixed with zero or more one-element lists. Like JavaScript, the
array postfix notation is used to access array elements as well as
struct or union fields. Value depends on the type of the addressed
location:
scalar | number |
struct | pointer |
union | pointer |
enum | atom |
pointer | pointer |
- c_store(:Location, +Value)
- Store a C value indirect at Location. See c_load/2 for the location
syntax. In addition to the conversions provided by c_load/2,
c_store/2 supports setting a struct field to a closure. Consider
the following declaration:
struct demo_func
{ int (*mul_i)(int, int);
};
We can initialise an instance of this structure holding a C function
pointer that calls the predicate mymul/3 as follows:
c_alloc(Ptr, struct(demo_func)),
c_store(Ptr[mul_i], mymul(int, int, [int])),
- c_cast(:Type, +PtrIn, -PtrOut)
- Cast a pointer. Type is one of:
- address
Unify PtrOut with an integer that reflects the address of the
pointer.
- Type[Count]
Create a pointer to Count elements of Type.
- Type
Create a pointer to an unknown number of elements of Type.
- c_nil(-Ptr) is det
- Unify Ptr with a (void) NULL pointer.
- c_is_nil(@Ptr) is semidet
- True when Ptr is a pointer object representing a NULL pointer.
- c_array_to_list(:Array, -List)
- Convert a C array indicated by a sized c_ptr
to a prolog list.
Examples:
% C int array to list
?- c_alloc(CPtr, int[]=[3,1,0,2]), c_array_to_list(CPtr,R).
CPtr = <C int[4]>(0x5629848165c0),
R = [3, 1, 0, 2].
- c_array_to_list(:Array, +Count, -List)
- Convert a C array indicated by a sized c_ptr
to a prolog list.
Examples:
% C int array to list
?- c_alloc(CPtr, int[]=[3,1,0,2]), c_array_to_list(CPtr,2,R).
CPtr = <C int[4]>(0x5629848165c0),
R = [3, 1, 0, 2].
- c_array_from_list(:Array, +List)
- Unify Array with a c_ptr that points
to a C array with the elements of List.
For now only numeric elements are supported.
Examples:
?- c_array_from_list(Ptr,[3,2,0]).
Ptr = <C long[3]>(0x55a265c6c3e0).
- c_array_from_list(:Array, +Count, -List)
- Unify Array with a c_ptr that points
to a C array with Count elements from List.
For now only numeric elements are supported.
Examples:
?- c_array_from_list(Ptr,2,[3,2,0]).
Ptr = <C long[2]>(0x55a265c494c0).
- c_array_to_compound(:Ptr, +Name, -Compound)
- Unify Compound with arguments obtained from the
C array pointed by the sized c_ptr Ptr.
Example
?- c_alloc(Arr,int[]=[3,0,1]), c_array_to_compound(Arr,myterm,C).
Arr = <C int[3]>(0x561f2497ff00),
C = myterm(3, 0, 1).
- c_array_to_compound(:Ptr, +Count, +Name, -Compound)
- Unify Compound with Count arguments obtained from the
C array pointed by the Ptr. Ptr can be an unsized
c_ptr (e.g. a c_ptr containing *int).
Example
?- c_alloc(Arr,int[]=[3,0,1]), c_array_to_compound(Arr,2,myterm,C).
Arr = <C int[3]>(0x561f2497fc00),
C = myterm(3, 0).
- c_array_from_compound(:Ptr, +Compound)
- Unify Ptr with an ffi blob c_ptr, which
points to a C array containing all the arguments
of the compount term Compound.
For now only numeric elements are supported.
Example
?- c_array_from_compound(Ptr,c(3,1,2)).
Ptr = <C long[3]>(0x561f248c6080).
- c_array_from_compound(:Ptr, +Count, +Compound)
- Like c_array_from_compound/2 but produce a C array
with only Count arguments from Compound.
For now only numeric elements are supported.
Example
?- c_array_from_compound(Ptr,2,c(3,1,2)).
Ptr = <C long[2]>(0x561f248a70c0).
- c_struct_dict(:Struct, ?Dict)
- Translate between a struct and a dict
- c_current_enum(?Name, :Enum, ?Int)
- True when Id is a member of Enum with Value.
- c_enum_in(+Name, :Enum, -Int) is det
- Convert an input element for an enum name to an integer.
- c_enum_out(-Name, :Enum, +Int) is det
- Convert an output element for an integer to an enum name.
- c_current_typedef(:Name, :Type) is nondet
- True when Name is a typedef name for Type.
- c_calloc(-Ptr, +Type, +Size, +Count) is det
- Allocate a chunk of memory similar to the C
calloc()
function. The
chunk is associated with the created Ptr, a blob of type c_ptr
(see blob/2). The content of the chunk is filled with 0-bytes. If
the blob is garbage collected by the atom garbage collector the
allocated chunk is freed.
- Arguments:
-
Type | - is the represented C type. It is either an atom or a term
of the shape struct(Name) , union(Name) or enum(Name) . The atomic
type name is not interpreted. See also c_typeof/2. |
Size | - is the size of a single element in bytes, i.e., should be
set to sizeof(Type) . As this low level function doesn't know how
large a structure or union is, this figure must be supplied by the
high level predicates. |
Count | - is the number of elements in the array. |
- c_alloc_string(-Ptr, +Data, +Encoding) is det
- Create a C
char
or wchar_t
string from Prolog text Data. Data is
an atom, string, code list, char list or integer. The text is
encoded according to Encoding, which is one of iso_latin_1
,
utf8
, octet
, text
or wchar_t
. The encodings octet
and
iso_latin_1
are synonym. The conversion may raise a
representation_error
exception if the encoding cannot represent
all code points in Data. The resulting string or wide string is
nul-terminated. Note that Data may contain code point 0 (zero). The
length of the string can be accessed using c_dim/3. The reported
length includes the terminating nul code.
This predicate is normally accessed through the high level interface
provided by c_alloc/2.
- c_free(+Ptr) is det
- Free the chunk associated with Ptr by calling the registered release
function immediately. This may be used to reduce the memory
foodprint without waiting for the atom garbage collector. The blob
itself can only be reclaimed by the atom garbage collector.
The type release function is non-NULL if the block as allocated
using c_alloc/2 or a function was associated with a pointer created
from an output argument or the foreign function return value using
the ~(Type, Free)
mechanism.
- c_disown(+Ptr) is det
- Clear the release function associated with the blob. This implies
that the block associated with the pointer is not released when the
blob is garbage collected. This can be used to transfer ownership of
a memory blob allocated using c_alloc/2 to the foreign application.
The foreign application must call PL_free() from the SWI-Prolog API
to release the memory. On systems where the heap is not associated
with a foreign module, the C library
free()
function may be used as
well. Using free()
works on all Unix systems we are aware of, but
does not work on Windows.
- c_load(+Ptr, +Offset, +Type, -Value) is det
- Fetch a C arithmetic value of Type at Offset from the pointer. Value
is unified with an integer or floating point number. If the size of
the chunk behind the pointer is known, Offset is validated to be
inside the chunk represented by Ptr. Pointers may
- c_load_string(+Ptr, -Data, +As, +Encoding) is det
- c_load_string(+Ptr, +Length, -Data, +As, +Encoding) is det
- Assuming Ptr points at text, either
char
or wchar_t
, extract the
value to Prolog. The c_load_string/4 variant assumes the text is
nul-terminated.
- Arguments:
-
As | - defines the resulting Prolog type and is one of atom ,
string , codes or chars |
Encoding | - is one of iso_latin_1 , octet , utf8 , text
or wchar_t . |
- c_offset(+Ptr0, +Offset, +Type, +Size, +Count, -Ptr) is det
- Get a pointer to some location inside the chunk Ptr0. This is
currently used to get a stand-alone pointer to a struct embedded in
another struct or a struct from an array of structs. Note that this
is not for accessing pointers inside a struct.
Creating a pointer inside an existing chunk increments the reference
count of Ptr0. Reclaiming the two pointers requires two atom garbage
collection cycles, one to reclaim the sub-pointer Ptr and one to
reclaim Ptr0.
The c_offset/5 primitive can also be used to cast a pointer, i.e.,
reinterpret its contents as if the pointer points at data of a
different type.
- c_store(+Ptr, +Offset, +Type, +Value) is det
- Store a C scalar value of type Type at Offset into Ptr. If Value is
a pointer, its reference count is incremented to ensure it is not
garbage collected before Ptr is garbage collected.
- c_typeof(+Ptr, -Type) is det
- True when Type is the Type used to create Ptr using c_calloc/4 or
c_offset/6.
- Arguments:
-
Type | - is an atom or term of the shape struct(Name) , union(Name)
or enum(Name) . Type may be mapped in zero or more *(Type) terms,
representing the levels of pointer indirection. |
- c_sizeof(+Type, -Bytes) is semidet
- True when Bytes is the size of the C scalar type Type. Only supports
basic C types. Fails silently on user defined types.
- c_alignof(+Type, -Bytes) is semidet
- True when Bytes is the mininal alignment for the C scalar type Type.
Only supports basic C types. Fails silently on user defined types.
This value is used to compute the layout of structs.
- c_address(+Ptr, -Address) is det
- True when Address is the (signed) integer address pointed at by Ptr.
- c_dim(+Ptr, -Count, -ElemSize) is det
- True when Ptr holds Count elements of size ElemSize. Both Count and
ElemSize are 0 (zero) if the value is not known.
The following predicates are exported, but not or incorrectly documented.