YAP 7.1.0
SWI-Prolog.h
1/* yap2swi.h */
2/*
3 * Project: SWI emulation for Yap Prolog
4 * Author: Steve Moyle and Vitor Santos Costa
5 * Email: steve.moyle@comlab.ox.ac.uk
6 * Date: 21 January 2002
7
8 * Copyright (c) 2002 Steve Moyle and Vitor Santos Costa. All rights reserved.
9
10
11*/
12
13#ifndef _FLI_H_INCLUDED
14#define _FLI_H_INCLUDED
15
16#ifdef __cplusplus
17extern "C" {
18#endif
19
20//=== includes ===============================================================
21#ifdef YAP_KERNEL
22#include "YapConfig.h"
23
24#ifdef __cplusplus
25#include <gmpxx.h>
26#else
27#include <gmp.h>
28#endif
29
30#ifdef __cplusplus
31extern "C" {
32#endif
33
34#include "YapInterface.h"
35#else
36#if _YAP_NOT_INSTALLED_
37#include <YapConfig.h>
38#include <YapInterface.h>
39#else
40#include <Yap/YapInterface.h>
41#endif
42#endif
43#include <stdarg.h>
44#include <stddef.h>
45#include <wchar.h>
46#if HAVE_TIME_H
47#include <time.h>
48#endif
49
50#if HAVE_STDBOOL_H
51
52#include <stdbool.h>
53
54#elif !defined(true)
55
56typedef int _Bool;
57
58#define bool _Bool
59
60#define true 1
61
62#define false 0
63
64#endif
65#ifndef __WINDOWS__
66#if defined(_MSC_VER) || defined(__MINGW32__)
67#define __WINDOWS__ 1
68#endif
69#endif
70
71#include "pl-types.h"
72
73/*******************************
74 * EXPORT *
75 *******************************/
76
77/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
78See SWI-Prolog.h, containing the same code for an explanation on this
79stuff.
80- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
81
82#define PL_EXPORT(type) extern X_API type
83#define PL_EXPORT_DATA(type) extern X_API type
84#define install_t O_API void
85
86/*******************************
87 * GCC ATTRIBUTES *
88 *******************************/
89
90#if __GNUC__ >= 4
91#define WUNUSED __attribute__((warn_unused_result))
92#else
93#define WUNUSED
94#endif
95
96#include "pl-types.h"
97typedef struct _PL_extension {
98 const char *predicate_name; /* Name of the predicate */
99 size_t arity; /* Arity of the predicate */
100 pl_function_t function; /* Implementing functions */
101 short flags; /* Or of PL_FA_... */
103
104#define PL_THREAD_NO_DEBUG 0x01 /* Start thread in nodebug mode */
105
106typedef struct {
107 unsigned long local_size; /* Stack sizes */
108 unsigned long global_size;
109 unsigned long trail_size;
110 unsigned long argument_size;
111 char *alias; /* alias name */
112 int (*cancel)(int id); /* cancel function */
113 intptr_t flags; /* PL_THREAD_* flags */
114 void *reserved[5]; /* reserved for extensions */
116
117typedef void *PL_engine_t;
118
119#define PL_FA_NOTRACE (0x01) /* foreign cannot be traced */
120#define PL_FA_TRANSPARENT (0x02) /* foreign is module transparent */
121#define PL_FA_NONDETERMINISTIC (0x04) /* foreign is non-deterministic */
122#define PL_FA_VARARGS (0x08) /* call using t0, ac, ctx */
123#define PL_FA_CREF (0x10) /* Internal: has clause-reference */
124#define PL_FA_ISO (0x20) /* Internal: ISO core predicate */
125
126/* begin from pl-itf.h */
127#define PL_VARIABLE (1) /* nothing */
128#define PL_ATOM (2) /* const char * */
129#define PL_INTEGER (3) /* int */
130#define PL_FLOAT (4) /* double */
131#define PL_STRING (5) /* const char * */
132#define PL_TERM (6)
133
134/* PL_unify_term() */
135#define PL_FUNCTOR (10) /* functor_t, arg ... */
136#define PL_LIST (11) /* length, arg ... */
137#define PL_CHARS (12) /* const char * */
138#define PL_POINTER (13) /* void * */
139 /* PlArg::PlArg(text, type) */
140#define PL_CODE_LIST (14) /* [ascii...] */
141#define PL_CHAR_LIST (15) /* [h,e,l,l,o] */
142#define PL_BOOL (16) /* PL_set_feature() */
143#define PL_FUNCTOR_CHARS (17) /* PL_unify_term() */
144#define PL_PREDICATE_INDICATOR (18) /* predicate_t (Procedure) */
145#define PL_SHORT (19) /* short */
146#define PL_INT (20) /* int */
147#define PL_LONG (21) /* long */
148#define PL_DOUBLE (22) /* double */
149#define PL_NCHARS (23) /* unsigned, const char * */
150#define PL_UTF8_CHARS (24) /* const char * */
151#define PL_UTF8_STRING (25) /* const char * */
152#define PL_INT64 (26) /* int64_t */
153#define PL_NUTF8_CHARS (27) /* unsigned, const char * */
154#define PL_NUTF8_CODES (29) /* unsigned, const char * */
155#define PL_NUTF8_STRING (30) /* unsigned, const char * */
156#define PL_NWCHARS (31) /* unsigned, const wchar_t * */
157#define PL_NWCODES (32) /* unsigned, const wchar_t * */
158#define PL_NWSTRING (33) /* unsigned, const wchar_t * */
159#define PL_MBCHARS (34) /* const char * */
160#define PL_MBCODES (35) /* const char * */
161#define PL_MBSTRING (36) /* const char * */
162#define PL_INTPTR (37) /* intptr_t */
163#define PL_CHAR (38) /* int */
164#define PL_CODE (39) /* int */
165#define PL_BYTE (40) /* int */
166 /* PL_skip_list() */
167#define PL_PARTIAL_LIST (41) /* a partial list */
168#define PL_CYCLIC_TERM (42) /* a cyclic list/term */
169#define PL_NOT_A_LIST (43) /* Object is not a list */
170
171/* Or'ed flags for PL_set_prolog_flag() */
172/* MUST fit in a short int! */
173#define FF_READONLY 0x1000 /* Read-only prolog flag */
174#define FF_KEEP \
175 0x2000 /* keep prolog flag if already se \
176t */
177#define FF_NOCREATE 0x4000 /* Fail if flag is non-existent */
178#define FF_MASK 0xf000
179
180#define CVT_ATOM 0x0001
181#define CVT_STRING 0x0002
182#define CVT_LIST 0x0004
183#define CVT_INTEGER 0x0008
184#define CVT_FLOAT 0x0010
185#define CVT_VARIABLE 0x0020
186#define CVT_NUMBER (CVT_INTEGER | CVT_FLOAT)
187#define CVT_ATOMIC (CVT_NUMBER | CVT_ATOM | CVT_STRING)
188#define CVT_WRITE 0x0040 /* as of version 3.2.10 */
189#define CVT_WRITE_CANONICAL 0x0080 /* as of version 3.2.10 */
190#define CVT_WRITEQ 0x00C0
191#define CVT_ALL (CVT_ATOMIC | CVT_LIST)
192#define CVT_MASK 0x00ff
193
194#define CVT_EXCEPTION 0x10000
195#define CVT_VARNOFAIL 0x20000 /* return 2 if argument is unbound */
196
197#define BUF_DISCARDABLE 0x0000
198#define BUF_RING 0x0100
199#define BUF_MALLOC 0x0200
200
201#define PL_ENGINE_MAIN ((PL_engine_t)0x1)
202#define PL_ENGINE_CURRENT ((PL_engine_t)0x2)
203
204#define PL_ENGINE_SET 0 /* engine set successfully */
205#define PL_ENGINE_INVAL 2 /* engine doesn't exist */
206#define PL_ENGINE_INUSE 3 /* engine is in use */
207
208#define PL_ACTION_TRACE 1 /* switch to trace mode */
209#define PL_ACTION_DEBUG 2 /* switch to debug mode */
210#define PL_ACTION_BACKTRACE 3 /* show a backtrace (stack dump) */
211#define PL_ACTION_BREAK 4 /* create a break environment */
212#define PL_ACTION_HALT 5 /* halt Prolog execution */
213#define PL_ACTION_ABORT 6 /* generate a Prolog abort */
214 /* 7: Obsolete PL_ACTION_SYMBOLFILE */
215#define PL_ACTION_WRITE 8 /* write via Prolog i/o buffer */
216#define PL_ACTION_FLUSH 9 /* Flush Prolog i/o buffer */
217#define PL_ACTION_GUIAPP 10 /* Win32: set when this is a gui */
218#define PL_ACTION_ATTACH_CONSOLE 11 /* MT: Attach a console */
219
220typedef enum {
221 FRG_FIRST_CALL = 0, /* Initial call */
222 FRG_CUTTED = 1, /* Context was cutted */
223 FRG_REDO = 2 /* Normal redo */
224} frg_code;
225
226struct foreign_context {
227 uintptr_t context; /* context value */
228 frg_code control; /* FRG_* action */
229 struct PL_local_data *engine; /* invoking engine */
230};
231
232typedef struct foreign_context *control_t;
233
234#define PRED_IMPL(name, arity, fname, flags) \
235 foreign_t pl_##fname##arity##_va(term_t PL__t0, int PL__ac, control_t PL__ctx)
236
237#define CTX_CNTRL ForeignControl(PL__ctx)
238#define CTX_PTR ForeignContextPtr(PL__ctx)
239#define CTX_INT ForeignContextInt(PL__ctx)
240#define CTX_ARITY PL__ac
241
242#define BeginPredDefs(id) const PL_extension PL_predicates_from_##id[] = {
243#define PRED_DEF(name, arity, fname, flags) \
244 {name, arity, pl_##fname##arity##_va, (flags) | PL_FA_VARARGS},
245#define EndPredDefs \
246 { NULL, 0, NULL, 0 } \
247 } \
248 ;
249
250#define FRG_REDO_MASK 0x00000003L
251#define FRG_REDO_BITS 2
252#define REDO_INT 0x02 /* Returned an integer */
253#define REDO_PTR 0x03 /* returned a pointer */
254
255#define ForeignRedoIntVal(v) (((uintptr_t)(v) << FRG_REDO_BITS) | REDO_INT)
256#define ForeignRedoPtrVal(v) (((uintptr_t)(v)) | REDO_PTR)
257
258#define ForeignRedoInt(v) return ForeignRedoIntVal(v)
259#define ForeignRedoPtr(v) return ForeignRedoPtrVal(v)
260
261#define ForeignControl(h) ((h)->control)
262#define ForeignContextInt(h) ((intptr_t)(h)->context)
263#define ForeignContextPtr(h) ((void *)(h)->context)
264#define ForeignEngine(h) ((h)->engine)
265
266#define FRG(n, a, f, flags) \
267 { n, a, f, flags }
268#define LFRG(n, a, f, flags) \
269 { n, a, f, flags }
270
271/* end from pl-itf.h */
272
273/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
274Output representation for PL_get_chars() and friends. The
275prepresentation type REP_FN is for PL_get_file_name() and friends. On
276Windows we use UTF-8 which is translated by the `XOS' layer to Windows
277UNICODE file functions.
278- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
279
280#define REP_ISO_LATIN_1 0x0000 /* output representation */
281#define REP_UTF8 0x1000
282#define REP_MB 0x2000
283#ifdef __WINDOWS__
284#define REP_FN REP_UTF8
285#else
286#define REP_FN REP_MB
287#endif
288
289#define PL_DIFF_LIST 0x20000 /* PL_unify_chars() */
290
291#ifdef SIO_MAGIC /* defined from <SWI-Stream.h> */
292
293/*******************************
294 * STREAM SUPPORT *
295 *******************************/
296
297/* Make IOSTREAM known to Prolog */
298#define PL_open_stream PL_unify_stream /* compatibility */
299PL_EXPORT(int) PL_unify_stream(term_t t, IOSTREAM *s);
300PL_EXPORT(int) PL_get_stream_handle(term_t t, IOSTREAM **s);
301PL_EXPORT(int) PL_release_stream(IOSTREAM *s);
302PL_EXPORT(IOSTREAM *)
303PL_open_resource(module_t m, const char *name, const char *rc_class,
304 const char *mode);
305
306PL_EXPORT(IOSTREAM *) * _PL_streams(void); /* base of streams */
307#ifndef PL_KERNEL
308#define Suser_input (_PL_streams()[0])
309#define Suser_output (_PL_streams()[1])
310#define Suser_error (_PL_streams()[2])
311#endif
312
313#define PL_WRT_QUOTED 0x01 /* quote atoms */
314#define PL_WRT_IGNOREOPS 0x02 /* ignore list/operators */
315#define PL_WRT_NUMBERVARS 0x04 /* print $VAR(N) as a variable */
316#define PL_WRT_PORTRAY 0x08 /* call portray */
317#define PL_WRT_CHARESCAPES 0x10 /* Output ISO escape sequences */
318#define PL_WRT_BACKQUOTED_STRING 0x20 /* Write strings as `...` */
319 /* Write attributed variables */
320#define PL_WRT_ATTVAR_IGNORE 0x040 /* Default: just write the var */
321#define PL_WRT_ATTVAR_DOTS 0x080 /* Write as Var{...} */
322#define PL_WRT_ATTVAR_WRITE 0x100 /* Write as Var{Attributes} */
323#define PL_WRT_ATTVAR_PORTRAY 0x200 /* Use Module:portray_attrs/2 */
324#define PL_WRT_ATTVAR_MASK \
325 (PL_WRT_ATTVAR_IGNORE | PL_WRT_ATTVAR_DOTS | PL_WRT_ATTVAR_WRITE | \
326 PL_WRT_ATTVAR_PORTRAY)
327#define PL_WRT_BLOB_PORTRAY 0x400 /* Use portray to emit non-text blobs */
328#define PL_WRT_NO_CYCLES 0x800 /* Never emit @(Template,Subst) */
329#define PL_WRT_LIST 0x1000 /* Write [...], even with ignoreops */
330#define PL_WRT_NEWLINE 0x2000 /* Add a newline */
331#define PL_WRT_VARNAMES 0x4000 /* Internal: variable_names(List) */
332
333PL_EXPORT(int)
334PL_write_term(IOSTREAM *s, term_t term, int precedence, int flags);
335
336/* PL_ttymode() results */
337#define PL_NOTTY 0 /* -tty in effect */
338#define PL_RAWTTY 1 /* get_single_char/1 */
339#define PL_COOKEDTTY 2 /* normal input */
340
341PL_EXPORT(int) PL_ttymode(IOSTREAM *s);
342
343#endif /*SIO_MAGIC*/
344
345PL_EXPORT(int) PL_chars_to_term(const char *chars, term_t term);
346
347/*******************************
348 * CALL-BACK *
349 *******************************/
350
351#ifdef PL_KERNEL
352#define PL_Q_DEBUG 0x01 /* = TRUE for backward compatibility */
353#endif
354#define PL_Q_NORMAL 0x02 /* normal usage */
355#define PL_Q_NODEBUG 0x04 /* use this one */
356#define PL_Q_CATCH_EXCEPTION 0x08 /* handle exceptions in C */
357#define PL_Q_PASS_EXCEPTION 0x10 /* pass to parent environment */
358#ifdef PL_KERNEL
359#define PL_Q_DETERMINISTIC 0x20 /* call was deterministic */
360#endif
361
362#define PL_fail return FALSE /* fail */
363#define PL_succeed return TRUE /* success */
364
365PL_EXPORT(PL_agc_hook_t) PL_agc_hook(PL_agc_hook_t);
366PL_EXPORT(char *) PL_atom_chars(atom_t);
367PL_EXPORT(char *) PL_atom_nchars(atom_t, size_t *);
368PL_EXPORT(term_t) PL_copy_term_ref(term_t);
369PL_EXPORT(term_t) PL_new_term_ref(void);
370PL_EXPORT(term_t) PL_new_term_refs(int);
371PL_EXPORT(void) PL_reset_term_refs(term_t);
372/* begin PL_get_* functions =============================*/
373PL_EXPORT(int) PL_get_arg(int, term_t, term_t);
374#define _PL_get_arg(Index,T,A) PL_get_arg(Index,T,A)
375PL_EXPORT(int) PL_get_atom(term_t, atom_t *);
376PL_EXPORT(int) PL_get_atom_chars(term_t, char **);
377PL_EXPORT(int) PL_get_atom_nchars(term_t, size_t *, char **);
378PL_EXPORT(int) PL_get_bool(term_t, int *);
379PL_EXPORT(int) PL_get_chars(term_t, char **, unsigned);
380PL_EXPORT(int) PL_get_nchars(term_t, size_t *, char **, unsigned);
381PL_EXPORT(int) PL_get_wchars(term_t, size_t *, wchar_t **, unsigned);
382PL_EXPORT(int) PL_get_functor(term_t, functor_t *);
383PL_EXPORT(int) PL_get_compound_name_arity(term_t t, atom_t *ap, size_t *ip);
384PL_EXPORT(int) PL_get_float(term_t, double *);
385PL_EXPORT(int) PL_get_head(term_t, term_t);
386PL_EXPORT(int) PL_get_int64(term_t, int64_t *);
387PL_EXPORT(int) PL_get_integer(term_t, int *);
388PL_EXPORT(int) PL_get_list(term_t, term_t, term_t);
389PL_EXPORT(int) PL_get_long(term_t, long *);
390PL_EXPORT(int) PL_get_list_chars(term_t, char **, unsigned);
391PL_EXPORT(int) PL_get_list_nchars(term_t, size_t *, char **, unsigned);
392PL_EXPORT(int) PL_get_module(term_t, module_t *);
393PL_EXPORT(module_t) PL_context(void);
394PL_EXPORT(int) PL_strip_module(term_t, module_t *, term_t);
395PL_EXPORT(atom_t) PL_module_name(module_t);
396PL_EXPORT(module_t) PL_new_module(atom_t);
397PL_EXPORT(int) PL_get_name_arity(term_t, atom_t *, size_t *);
398PL_EXPORT(int) PL_get_nil(term_t);
399PL_EXPORT(int) PL_get_pointer(term_t, void **);
400PL_EXPORT(int) PL_get_intptr(term_t, intptr_t *);
401PL_EXPORT(int) PL_get_uintptr(term_t, uintptr_t *);
402PL_EXPORT(int) PL_get_tail(term_t, term_t);
403/* end PL_get_* functions =============================*/
404/* begin PL_new_* functions =============================*/
405PL_EXPORT(atom_t) PL_new_atom(const char *);
406PL_EXPORT(atom_t) PL_new_atom_nchars(size_t, const char *);
407PL_EXPORT(atom_t) PL_new_atom_wchars(size_t, const pl_wchar_t *);
408PL_EXPORT(char *) PL_atom_nchars(atom_t, size_t *);
409PL_EXPORT(pl_wchar_t *) PL_atom_wchars(atom_t, size_t *);
410PL_EXPORT(functor_t) PL_new_functor(atom_t, size_t);
411PL_EXPORT(atom_t) PL_functor_name(functor_t);
412PL_EXPORT(size_t) PL_functor_arity(functor_t);
413/* end PL_new_* functions =============================*/
414/* begin PL_put_* functions =============================*/
415PL_EXPORT(int) PL_cons_functor(term_t, functor_t, ...);
416PL_EXPORT(int) PL_cons_functor_v(term_t, functor_t, term_t);
417PL_EXPORT(int) PL_cons_list(term_t, term_t, term_t);
418PL_EXPORT(int) PL_put_atom(term_t, atom_t);
419PL_EXPORT(int) PL_put_atom_chars(term_t, const char *);
420PL_EXPORT(int) PL_put_atom_nchars(term_t, size_t, const char *);
421PL_EXPORT(int) PL_put_boolean(term_t, uintptr_t);
422PL_EXPORT(int) PL_put_float(term_t, double);
423PL_EXPORT(int) PL_put_functor(term_t, functor_t t);
424PL_EXPORT(int) PL_put_int64(term_t, int64_t);
425PL_EXPORT(int) PL_put_integer(term_t, long);
426PL_EXPORT(int) PL_put_list(term_t);
427PL_EXPORT(int) PL_put_list_chars(term_t, const char *);
428PL_EXPORT(int) PL_put_nil(term_t);
429PL_EXPORT(int) PL_put_pointer(term_t, void *);
430PL_EXPORT(int) PL_put_string_chars(term_t, const char *);
431PL_EXPORT(int) PL_put_string_nchars(term_t, size_t, const char *);
432PL_EXPORT(int) PL_put_term(term_t, term_t);
433PL_EXPORT(int) PL_put_variable(term_t);
434PL_EXPORT(int) PL_put_intptr(term_t t, intptr_t n);
435PL_EXPORT(int) PL_put_uintptr(term_t t, uintptr_t n);
436PL_EXPORT(int) PL_compare(term_t, term_t);
437/* end PL_put_* functions =============================*/
438/* begin PL_unify_* functions =============================*/
439PL_EXPORT(int) PL_unify(term_t, term_t);
440PL_EXPORT(int) PL_unify_atom(term_t, atom_t);
441PL_EXPORT(int) PL_unify_arg(int, term_t, term_t);
442PL_EXPORT(int) PL_unify_atom_chars(term_t, const char *);
443PL_EXPORT(int) PL_unify_atom_nchars(term_t, size_t len, const char *);
444PL_EXPORT(int) PL_unify_float(term_t, double);
445PL_EXPORT(int) PL_unify_functor(term_t, functor_t);
446PL_EXPORT(int) PL_unify_int64(term_t, int64_t);
447PL_EXPORT(int) PL_unify_intptr(term_t, intptr_t);
448PL_EXPORT(int) PL_unify_uintptr(term_t, uintptr_t);
449PL_EXPORT(int) PL_unify_integer(term_t, long int);
450PL_EXPORT(int) PL_unify_list(term_t, term_t, term_t);
451PL_EXPORT(int) PL_unify_list_chars(term_t, const char *);
452PL_EXPORT(int) PL_unify_list_ncodes(term_t, size_t, const char *);
453PL_EXPORT(int) PL_unify_nil(term_t);
454PL_EXPORT(int) PL_unify_pointer(term_t, void *);
455PL_EXPORT(int) PL_unify_bool(term_t, int);
456PL_EXPORT(int) PL_unify_string_chars(term_t, const char *);
457PL_EXPORT(int) PL_unify_string_nchars(term_t, size_t, const char *);
458PL_EXPORT(int) PL_unify_term(term_t, ...);
459PL_EXPORT(int) PL_unify_chars(term_t, int, size_t, const char *);
460PL_EXPORT(int) PL_unify_chars_diff(term_t, term_t, int, size_t, const char *);
461/*******************************
462 * LISTS *
463 *******************************/
464
465PL_EXPORT(int) PL_skip_list(term_t list, term_t tail, size_t *len);
466
467PL_EXPORT(int) PL_unify_wchars(term_t, int, size_t, const pl_wchar_t *);
468PL_EXPORT(int)
469PL_unify_wchars_diff(term_t, term_t, int, size_t, const pl_wchar_t *);
470PL_EXPORT(int) PL_chars_to_term(const char *, term_t);
471/* begin PL_is_* functions =============================*/
472PL_EXPORT(int) PL_is_atom(term_t);
473PL_EXPORT(int) PL_is_atomic(term_t);
474PL_EXPORT(int) PL_is_compound(term_t);
475PL_EXPORT(int) PL_is_float(term_t);
476PL_EXPORT(int) PL_is_functor(term_t, functor_t);
477PL_EXPORT(int) PL_is_ground(term_t);
478PL_EXPORT(int) PL_is_callable(term_t);
479PL_EXPORT(int) PL_is_integer(term_t);
480PL_EXPORT(int) PL_is_pair(term_t);
481PL_EXPORT(int) PL_is_list(term_t);
482PL_EXPORT(int) PL_is_pair(term_t);
483PL_EXPORT(int) PL_is_number(term_t);
484PL_EXPORT(int) PL_is_string(term_t);
485PL_EXPORT(int) PL_is_variable(term_t);
486PL_EXPORT(int) PL_term_type(term_t);
487PL_EXPORT(int) PL_is_inf(term_t);
488PL_EXPORT(int) PL_is_acyclic(term_t t);
489/* end PL_is_* functions =============================*/
490PL_EXPORT(void) PL_halt(int);
491PL_EXPORT(int) PL_initialise(int, char **);
492PL_EXPORT(int) PL_is_initialised(int *, char ***);
493PL_EXPORT(void) PL_close_foreign_frame(fid_t);
494PL_EXPORT(void) PL_discard_foreign_frame(fid_t);
495PL_EXPORT(void) PL_rewind_foreign_frame(fid_t);
496PL_EXPORT(fid_t) PL_open_foreign_frame(void);
497#define PL_raise_exception(t) PL_raise_exception__( __FILE__, __FUNCTION__, __LINE__, t)
498
499 PL_EXPORT(int) PL_raise_exception__(const char *, const char *, int,term_t);
500PL_EXPORT(int) PL_throw(term_t);
501PL_EXPORT(void) PL_clear_exception(void);
502PL_EXPORT(void) PL_register_atom(atom_t);
503PL_EXPORT(void) PL_unregister_atom(atom_t);
504PL_EXPORT(predicate_t) PL_pred(functor_t, module_t);
505PL_EXPORT(predicate_t) PL_predicate(const char *, size_t, const char *);
506#define GP_NAMEARITY 0x100 /* or'ed mask */
507PL_EXPORT(int) PL_unify_predicate(term_t head, predicate_t pred, int how);
508PL_EXPORT(void) PL_predicate_info(predicate_t, atom_t *, size_t *, module_t *);
509PL_EXPORT(qid_t) PL_open_query(module_t, int, predicate_t, term_t);
510PL_EXPORT(int) PL_next_solution(qid_t);
511PL_EXPORT(void) PL_cut_query(qid_t);
512PL_EXPORT(qid_t) PL_current_query(void);
513PL_EXPORT(void) PL_close_query(qid_t);
514PL_EXPORT(int) PL_toplevel(void);
515PL_EXPORT(term_t) PL_exception(qid_t);
516PL_EXPORT(term_t) PL_exception(qid_t);
517PL_EXPORT(int) PL_call_predicate(module_t, int, predicate_t, term_t);
518PL_EXPORT(int) PL_call(term_t, module_t);
519PL_EXPORT(void) PL_register_foreign(const char *, size_t, pl_function_t, int);
520PL_EXPORT(void)
521PL_register_foreign_in_module(const char *, const char *, size_t, pl_function_t,
522 int);
523PL_EXPORT(void) PL_register_extensions(const PL_extension *);
524PL_EXPORT(void)
525PL_register_extensions_in_module(const char *module, const PL_extension *);
526PL_EXPORT(void) PL_load_extensions(const PL_extension *);
527PL_EXPORT(int) PL_handle_signals(void);
528PL_EXPORT(int) PL_thread_self(void);
529PL_EXPORT(int) PL_unify_thread_id(term_t, int);
530PL_EXPORT(int) PL_thread_attach_engine(const PL_thread_attr_t *);
531PL_EXPORT(int) PL_thread_destroy_engine(void);
532PL_EXPORT(int) PL_thread_at_exit(void (*)(void *), void *, int);
533PL_EXPORT(int) PL_thread_raise(int tid, int sig);
534PL_EXPORT(PL_engine_t) PL_create_engine(const PL_thread_attr_t *);
535PL_EXPORT(int) PL_destroy_engine(PL_engine_t);
536PL_EXPORT(int) PL_set_engine(PL_engine_t, PL_engine_t *);
537PL_EXPORT(int) PL_get_string(term_t, char **, size_t *);
538PL_EXPORT(int) PL_get_string_chars(term_t, char **, size_t *);
539PL_EXPORT(record_t) PL_record(term_t);
540PL_EXPORT(int) PL_recorded(record_t, term_t);
541PL_EXPORT(record_t) PL_duplicate_record(record_t);
542PL_EXPORT(void) PL_erase(record_t);
543/* only partial implementation, does not guarantee export between different
544 * architectures and versions of YAP */
545PL_EXPORT(char *) PL_record_external(term_t, size_t *);
546PL_EXPORT(int) PL_recorded_external(const char *, term_t);
547PL_EXPORT(int) PL_erase_external(char *);
548PL_EXPORT(int) PL_action(int, ...);
549PL_EXPORT(void) PL_on_halt(int (*)(int, void *), void *);
550PL_EXPORT(void *) PL_malloc(size_t);
551PL_EXPORT(void *) PL_malloc_uncollectable(size_t s);
552PL_EXPORT(void *) PL_realloc(void *, size_t);
553PL_EXPORT(void) PL_free(void *);
554PL_EXPORT(int) PL_eval_expression_to_int64_ex(term_t t, int64_t *val);
555PL_EXPORT(void) PL_cleanup_fork(void);
556PL_EXPORT(int) PL_get_signum_ex(term_t sig, int *n);
557
558PL_EXPORT(size_t) PL_utf8_strlen(const char *s, size_t len);
559
560PL_EXPORT(int) PL_unify_list_codes(term_t l, const char *chas);
561
562PL_EXPORT(void) PL_add_to_protocol(const char *buf, size_t count);
563
564#define PL_SIGSYNC 0x00010000 /* call handler synchronously */
565#define PL_SIGNOFRAME 0x00020000 /* Do not create a Prolog frame */
566
567extern X_API void (*PL_signal(int sig, void (*func)(int)))(int);
568extern X_API void PL_fatal_error(const char *msg);
569
570extern X_API int Sprintf(const char *fm, ...);
571extern X_API int Sdprintf(const char *, ...);
572
573/*******************************
574 * FILENAME SUPPORT *
575 *******************************/
576
577#define PL_FILE_ABSOLUTE 0x01 /* return absolute path */
578#define PL_FILE_OSPATH 0x02 /* return path in OS notation */
579#define PL_FILE_SEARCH 0x04 /* use file_search_path */
580#define PL_FILE_EXIST 0x08 /* demand file to exist */
581#define PL_FILE_READ 0x10 /* demand read-access */
582#define PL_FILE_WRITE 0x20 /* demand write-access */
583#define PL_FILE_EXECUTE 0x40 /* demand execute-access */
584#define PL_FILE_NOERRORS 0x80 /* do not raise exceptions */
585
586PL_EXPORT(int) PL_get_file_name(term_t n, char **name, int flags);
587PL_EXPORT(int) PL_get_file_nameW(term_t n, wchar_t **name, int flags);
588PL_EXPORT(void) PL_changed_cwd(void); /* foreign code changed CWD */
589PL_EXPORT(char *) PL_cwd(char *buf, size_t buflen);
590
591/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
592NOTE: the functions in this section are not documented, as as yet not
593adviced for public usage. They are intended to provide an abstract
594interface for the GNU readline interface as defined in pl-rl.c. This
595abstract interface is necessary to make an embeddable system without the
596readline overhead.
597- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
598/* PL_dispatch() modes */
599#define PL_DISPATCH_NOWAIT 0 /* Dispatch only once */
600#define PL_DISPATCH_WAIT 1 /* Dispatch till input available */
601#define PL_DISPATCH_INSTALLED 2 /* dispatch function installed? */
602
603PL_EXPORT(int) PL_dispatch(int fd, int wait);
604PL_EXPORT(PL_dispatch_hook_t) PL_dispatch_hook(PL_dispatch_hook_t);
605PL_EXPORT(void) PL_add_to_protocol(const char *buf, size_t count);
606PL_EXPORT(char *) PL_prompt_string(int fd);
607PL_EXPORT(void) PL_write_prompt(int dowrite);
608PL_EXPORT(void) PL_prompt_next(int fd);
609PL_EXPORT(char *) PL_atom_generator(const char *prefix, int state);
610PL_EXPORT(pl_wchar_t *)
611PL_atom_generator_w(const pl_wchar_t *pref, pl_wchar_t *buffer, size_t buflen,
612 int state);
613
614/*******************************
615 * WINDOWS MESSAGES *
616 *******************************/
617
618#if defined(_MSC_VER) || defined(__MINGW32__) /* <windows.h> is included */
619#define PL_MSG_EXCEPTION_RAISED -1
620#define PL_MSG_IGNORED 0
621#define PL_MSG_HANDLED 1
622
623#ifdef Bind
624#undef Bind
625#endif
626#include <windows.h>
627
628PL_EXPORT(LRESULT)
629PL_win_message_proc(HWND hwnd, UINT message,
630 // WPARAM wParam,
631 LPARAM lParam);
632#endif /*_WINDOWS_*/
633
634/********************************
635 * QUERY PROLOG *
636 *********************************/
637
638#define PL_QUERY_ARGC 1 /* return main() argc */
639#define PL_QUERY_ARGV 2 /* return main() argv */
640 /* 3: Obsolete PL_QUERY_SYMBOLFILE */
641 /* 4: Obsolete PL_QUERY_ORGSYMBOLFILE*/
642#define PL_QUERY_GETC 5 /* Read character from terminal */
643#define PL_QUERY_MAX_INTEGER 6 /* largest integer */
644#define PL_QUERY_MIN_INTEGER 7 /* smallest integer */
645#define PL_QUERY_MAX_TAGGED_INT 8 /* largest tagged integer */
646#define PL_QUERY_MIN_TAGGED_INT 9 /* smallest tagged integer */
647#define PL_QUERY_VERSION 10 /* 207006 = 2.7.6 */
648#define PL_QUE_MAX_THREADS 11 /* maximum thread count */
649#define PL_QUERY_ENCODING 12 /* I/O encoding */
650#define PL_QUERY_USER_CPU 13 /* User CPU in milliseconds */
651#define PL_QUERY_HALTING 14 /* If TRUE, we are in PL_cleanup() */
652
653X_API intptr_t PL_query(int); /* get information from Prolog */
654
655/*******************************
656 * ERRORS *
657 *******************************/
658
659PL_EXPORT(int) PL_get_atom_ex(term_t t, atom_t *a);
660PL_EXPORT(int) PL_get_integer_ex(term_t t, int *i);
661PL_EXPORT(int) PL_get_long_ex(term_t t, long *i);
662PL_EXPORT(int) PL_get_int64_ex(term_t t, int64_t *i);
663PL_EXPORT(int) PL_get_intptr_ex(term_t t, intptr_t *i);
664PL_EXPORT(int) PL_get_size_ex(term_t t, size_t *i);
665PL_EXPORT(int) PL_get_bool_ex(term_t t, int *i);
666PL_EXPORT(int) PL_get_float_ex(term_t t, double *f);
667PL_EXPORT(int) PL_get_char_ex(term_t t, int *p, int eof);
668PL_EXPORT(int) PL_unify_bool_ex(term_t t, int val);
669PL_EXPORT(int) PL_get_pointer_ex(term_t t, void **addrp);
670PL_EXPORT(int) PL_unify_list_ex(term_t l, term_t h, term_t t);
671PL_EXPORT(int) PL_unify_nil_ex(term_t l);
672PL_EXPORT(int) PL_get_list_ex(term_t l, term_t h, term_t t);
673PL_EXPORT(int) PL_get_nil_ex(term_t l);
674
675PL_EXPORT(int) PL_instantiation_error(term_t culprit);
676PL_EXPORT(int) PL_uninstantiation_error(term_t culprit);
677PL_EXPORT(int) PL_representation_error(const char *resource);
678PL_EXPORT(int) PL_type_error(const char *expected, term_t culprit);
679PL_EXPORT(int) PL_domain_error(const char *expected, term_t culprit);
680PL_EXPORT(int) PL_existence_error(const char *type, term_t culprit);
681PL_EXPORT(int)
682PL_permission_error(const char *operation, const char *type, term_t culprit);
683PL_EXPORT(int) PL_resource_error(const char *resource);
684
685/*******************************
686 * PROLOG FLAGS *
687 *******************************/
688
689#define PL_set_feature PL_set_prolog_flag /* compatibility */
690PL_EXPORT(int) PL_set_prolog_flag(const char *name, int type, ...);
691
692#include "YapBlobs.h"
693
694PL_EXPORT(void *) PL_blob_data(atom_t a, size_t *len, PL_blob_t **type);
695PL_EXPORT(int) PL_unify_blob(term_t t, void *blob, size_t len, PL_blob_t *type);
696
697#if !defined(__cplusplus)
698
699#include <gmp.h>
700
701 PL_EXPORT(int) PL_get_mpz(term_t t, mpz_t mpz);
702PL_EXPORT(int) PL_unify_mpz(term_t t, mpz_t mpz);
703PL_EXPORT(int) PL_get_mpq(term_t t, mpq_t mpz);
704PL_EXPORT(int) PL_unify_mpq(term_t t, mpq_t mpz);
705
706#endif
707
708PL_EXPORT(int) PL_current_prolog_flag(atom_t name, int type, void *ptr);
709
710void swi_install(void);
711
712X_API int PL_warning(const char *msg, ...);
713
714/********************************
715 * NON-DETERMINISTIC CALL/RETURN *
716 *********************************/
717
718/* Note 1: Non-deterministic foreign functions may also use the deterministic
719 return methods PL_succeed and PL_fail.
720
721 Note 2: The argument to PL_retry is a sizeof(ptr)-2 bits signed
722 integer (use type intptr_t).
723*/
724
725#define PL_FIRST_CALL (0)
726#define PL_CUTTED (1) /* deprecated */
727#define PL_PRUNED (1)
728#define PL_REDO (2)
729
730#define PL_retry(n) return _PL_retry(n)
731#define PL_retry_address(a) return _PL_retry_address(a)
732
733PL_EXPORT(foreign_t) _PL_retry(intptr_t);
734PL_EXPORT(foreign_t) _PL_retry_address(void *);
735PL_EXPORT(int) PL_foreign_control(control_t);
736PL_EXPORT(intptr_t) PL_foreign_context(control_t);
737PL_EXPORT(void *) PL_foreign_context_address(control_t);
739typedef struct SWI_IO {
740 functor_t f;
741 void *get_c;
742 void *put_c;
743 void *get_w;
744 void *put_w;
745 void *flush_s;
746 void *close_s;
747 void *get_stream_handle;
748 void *get_stream_position;
750
751/* SWI stream info */
752PL_EXPORT(void) PL_YAP_InitSWIIO(struct SWI_IO *swio);
753
754#ifdef __cplusplus
755}
756#endif
757
758#endif /* _FLI_H_INCLUDED */
759
760#ifdef __WINDOWS__
761X_API int PL_w32thread_raise(DWORD id, int sig);
762#endif
A matrix.
Definition: matrix.c:68
Module property: low-level data used to manage modes.
Definition: Yatom.h:209
Definition: Yatom.h:544